{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Telegram.Bot.API.Types where
import Data.Aeson (ToJSON(..), FromJSON(..), Value(..), object, KeyValue ((.=)), withObject, (.:))
import Data.Aeson.Types (Parser, Pair, Object)
import Data.Aeson.Text (encodeToLazyText)
import Data.Coerce (coerce)
import Data.Bool (bool)
import Data.Maybe (catMaybes)
import Data.Functor ((<&>))
import Data.Hashable (Hashable)
import Data.String
import Data.Text (Text, pack)
import qualified Data.Text as Text
import qualified Data.Text.Lazy as TL
import Data.Time.Clock.POSIX (POSIXTime)
import GHC.Generics (Generic)
import Servant.API
import Servant.Multipart.API
import System.FilePath
import Telegram.Bot.API.Internal.Utils
type RequiredQueryParam = QueryParam' '[Required , Strict]
newtype Seconds = Seconds Int
deriving (Seconds -> Seconds -> Bool
(Seconds -> Seconds -> Bool)
-> (Seconds -> Seconds -> Bool) -> Eq Seconds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Seconds -> Seconds -> Bool
$c/= :: Seconds -> Seconds -> Bool
== :: Seconds -> Seconds -> Bool
$c== :: Seconds -> Seconds -> Bool
Eq, Int -> Seconds -> ShowS
[Seconds] -> ShowS
Seconds -> String
(Int -> Seconds -> ShowS)
-> (Seconds -> String) -> ([Seconds] -> ShowS) -> Show Seconds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seconds] -> ShowS
$cshowList :: [Seconds] -> ShowS
show :: Seconds -> String
$cshow :: Seconds -> String
showsPrec :: Int -> Seconds -> ShowS
$cshowsPrec :: Int -> Seconds -> ShowS
Show, Integer -> Seconds
Seconds -> Seconds
Seconds -> Seconds -> Seconds
(Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Seconds -> Seconds)
-> (Integer -> Seconds)
-> Num Seconds
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Seconds
$cfromInteger :: Integer -> Seconds
signum :: Seconds -> Seconds
$csignum :: Seconds -> Seconds
abs :: Seconds -> Seconds
$cabs :: Seconds -> Seconds
negate :: Seconds -> Seconds
$cnegate :: Seconds -> Seconds
* :: Seconds -> Seconds -> Seconds
$c* :: Seconds -> Seconds -> Seconds
- :: Seconds -> Seconds -> Seconds
$c- :: Seconds -> Seconds -> Seconds
+ :: Seconds -> Seconds -> Seconds
$c+ :: Seconds -> Seconds -> Seconds
Num, [Seconds] -> Encoding
[Seconds] -> Value
Seconds -> Encoding
Seconds -> Value
(Seconds -> Value)
-> (Seconds -> Encoding)
-> ([Seconds] -> Value)
-> ([Seconds] -> Encoding)
-> ToJSON Seconds
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Seconds] -> Encoding
$ctoEncodingList :: [Seconds] -> Encoding
toJSONList :: [Seconds] -> Value
$ctoJSONList :: [Seconds] -> Value
toEncoding :: Seconds -> Encoding
$ctoEncoding :: Seconds -> Encoding
toJSON :: Seconds -> Value
$ctoJSON :: Seconds -> Value
ToJSON, Value -> Parser [Seconds]
Value -> Parser Seconds
(Value -> Parser Seconds)
-> (Value -> Parser [Seconds]) -> FromJSON Seconds
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Seconds]
$cparseJSONList :: Value -> Parser [Seconds]
parseJSON :: Value -> Parser Seconds
$cparseJSON :: Value -> Parser Seconds
FromJSON)
data User = User
{ User -> UserId
userId :: UserId
, User -> Bool
userIsBot :: Bool
, User -> Text
userFirstName :: Text
, User -> Maybe Text
userLastName :: Maybe Text
, User -> Maybe Text
userUsername :: Maybe Text
, User -> Maybe Text
userLanguageCode :: Maybe Text
, User -> Maybe Bool
userCanJoinGroups :: Maybe Bool
, User -> Maybe Bool
userCanReadAllGroupMessages :: Maybe Bool
, User -> Maybe Bool
userSupportsInlineQueries :: Maybe Bool
}
deriving (Int -> User -> ShowS
[User] -> ShowS
User -> String
(Int -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: Int -> User -> ShowS
$cshowsPrec :: Int -> User -> ShowS
Show, (forall x. User -> Rep User x)
-> (forall x. Rep User x -> User) -> Generic User
forall x. Rep User x -> User
forall x. User -> Rep User x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep User x -> User
$cfrom :: forall x. User -> Rep User x
Generic)
newtype UserId = UserId Integer
deriving (UserId -> UserId -> Bool
(UserId -> UserId -> Bool)
-> (UserId -> UserId -> Bool) -> Eq UserId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserId -> UserId -> Bool
$c/= :: UserId -> UserId -> Bool
== :: UserId -> UserId -> Bool
$c== :: UserId -> UserId -> Bool
Eq, Int -> UserId -> ShowS
[UserId] -> ShowS
UserId -> String
(Int -> UserId -> ShowS)
-> (UserId -> String) -> ([UserId] -> ShowS) -> Show UserId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserId] -> ShowS
$cshowList :: [UserId] -> ShowS
show :: UserId -> String
$cshow :: UserId -> String
showsPrec :: Int -> UserId -> ShowS
$cshowsPrec :: Int -> UserId -> ShowS
Show, [UserId] -> Encoding
[UserId] -> Value
UserId -> Encoding
UserId -> Value
(UserId -> Value)
-> (UserId -> Encoding)
-> ([UserId] -> Value)
-> ([UserId] -> Encoding)
-> ToJSON UserId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [UserId] -> Encoding
$ctoEncodingList :: [UserId] -> Encoding
toJSONList :: [UserId] -> Value
$ctoJSONList :: [UserId] -> Value
toEncoding :: UserId -> Encoding
$ctoEncoding :: UserId -> Encoding
toJSON :: UserId -> Value
$ctoJSON :: UserId -> Value
ToJSON, Value -> Parser [UserId]
Value -> Parser UserId
(Value -> Parser UserId)
-> (Value -> Parser [UserId]) -> FromJSON UserId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [UserId]
$cparseJSONList :: Value -> Parser [UserId]
parseJSON :: Value -> Parser UserId
$cparseJSON :: Value -> Parser UserId
FromJSON)
instance ToHttpApiData UserId where
toUrlPiece :: UserId -> Text
toUrlPiece = String -> Text
pack (String -> Text) -> (UserId -> String) -> UserId -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Show Integer => Integer -> String
forall a. Show a => a -> String
show @Integer (Integer -> String) -> (UserId -> Integer) -> UserId -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UserId -> Integer
coerce
data Chat = Chat
{ Chat -> ChatId
chatId :: ChatId
, Chat -> ChatType
chatType :: ChatType
, Chat -> Maybe Text
chatTitle :: Maybe Text
, Chat -> Maybe Text
chatUsername :: Maybe Text
, Chat -> Maybe Text
chatFirstName :: Maybe Text
, Chat -> Maybe Text
chatLastName :: Maybe Text
, Chat -> Maybe ChatPhoto
chatPhoto :: Maybe ChatPhoto
, Chat -> Maybe Text
chatBio :: Maybe Text
, Chat -> Maybe Bool
chatHasPrivateForwards :: Maybe Bool
, Chat -> Maybe Text
chatDescription :: Maybe Text
, Chat -> Maybe Text
chatInviteLink :: Maybe Text
, Chat -> Maybe Message
chatPinnedMessage :: Maybe Message
, Chat -> Maybe ChatPermissions
chatPermissions :: Maybe ChatPermissions
, Chat -> Maybe Int
chatSlowModeDelay :: Maybe Int
, Chat -> Maybe POSIXTime
chatMessageAutoDeleteTime :: Maybe POSIXTime
, Chat -> Maybe Bool
chatHasProtectedContent :: Maybe Bool
, Chat -> Maybe Text
chatStickerSetName :: Maybe Text
, Chat -> Maybe Bool
chatCanSetStickerSet :: Maybe Bool
, Chat -> Maybe ChatId
chatLinkedChatId :: Maybe ChatId
, Chat -> Maybe ChatLocation
chatLocation :: Maybe ChatLocation
}
deriving ((forall x. Chat -> Rep Chat x)
-> (forall x. Rep Chat x -> Chat) -> Generic Chat
forall x. Rep Chat x -> Chat
forall x. Chat -> Rep Chat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Chat x -> Chat
$cfrom :: forall x. Chat -> Rep Chat x
Generic, Int -> Chat -> ShowS
[Chat] -> ShowS
Chat -> String
(Int -> Chat -> ShowS)
-> (Chat -> String) -> ([Chat] -> ShowS) -> Show Chat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chat] -> ShowS
$cshowList :: [Chat] -> ShowS
show :: Chat -> String
$cshow :: Chat -> String
showsPrec :: Int -> Chat -> ShowS
$cshowsPrec :: Int -> Chat -> ShowS
Show)
newtype ChatId = ChatId Integer
deriving (ChatId -> ChatId -> Bool
(ChatId -> ChatId -> Bool)
-> (ChatId -> ChatId -> Bool) -> Eq ChatId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatId -> ChatId -> Bool
$c/= :: ChatId -> ChatId -> Bool
== :: ChatId -> ChatId -> Bool
$c== :: ChatId -> ChatId -> Bool
Eq, Int -> ChatId -> ShowS
[ChatId] -> ShowS
ChatId -> String
(Int -> ChatId -> ShowS)
-> (ChatId -> String) -> ([ChatId] -> ShowS) -> Show ChatId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatId] -> ShowS
$cshowList :: [ChatId] -> ShowS
show :: ChatId -> String
$cshow :: ChatId -> String
showsPrec :: Int -> ChatId -> ShowS
$cshowsPrec :: Int -> ChatId -> ShowS
Show, [ChatId] -> Encoding
[ChatId] -> Value
ChatId -> Encoding
ChatId -> Value
(ChatId -> Value)
-> (ChatId -> Encoding)
-> ([ChatId] -> Value)
-> ([ChatId] -> Encoding)
-> ToJSON ChatId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ChatId] -> Encoding
$ctoEncodingList :: [ChatId] -> Encoding
toJSONList :: [ChatId] -> Value
$ctoJSONList :: [ChatId] -> Value
toEncoding :: ChatId -> Encoding
$ctoEncoding :: ChatId -> Encoding
toJSON :: ChatId -> Value
$ctoJSON :: ChatId -> Value
ToJSON, Value -> Parser [ChatId]
Value -> Parser ChatId
(Value -> Parser ChatId)
-> (Value -> Parser [ChatId]) -> FromJSON ChatId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ChatId]
$cparseJSONList :: Value -> Parser [ChatId]
parseJSON :: Value -> Parser ChatId
$cparseJSON :: Value -> Parser ChatId
FromJSON, Eq ChatId
Eq ChatId
-> (Int -> ChatId -> Int) -> (ChatId -> Int) -> Hashable ChatId
Int -> ChatId -> Int
ChatId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: ChatId -> Int
$chash :: ChatId -> Int
hashWithSalt :: Int -> ChatId -> Int
$chashWithSalt :: Int -> ChatId -> Int
$cp1Hashable :: Eq ChatId
Hashable)
instance ToHttpApiData ChatId where
toUrlPiece :: ChatId -> Text
toUrlPiece ChatId
a = String -> Text
pack (String -> Text) -> (Integer -> String) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Show Integer => Integer -> String
forall a. Show a => a -> String
show @Integer (Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ ChatId -> Integer
coerce ChatId
a
data ChatType
= ChatTypePrivate
| ChatTypeGroup
| ChatTypeSupergroup
| ChatTypeChannel
deriving ((forall x. ChatType -> Rep ChatType x)
-> (forall x. Rep ChatType x -> ChatType) -> Generic ChatType
forall x. Rep ChatType x -> ChatType
forall x. ChatType -> Rep ChatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatType x -> ChatType
$cfrom :: forall x. ChatType -> Rep ChatType x
Generic, Int -> ChatType -> ShowS
[ChatType] -> ShowS
ChatType -> String
(Int -> ChatType -> ShowS)
-> (ChatType -> String) -> ([ChatType] -> ShowS) -> Show ChatType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatType] -> ShowS
$cshowList :: [ChatType] -> ShowS
show :: ChatType -> String
$cshow :: ChatType -> String
showsPrec :: Int -> ChatType -> ShowS
$cshowsPrec :: Int -> ChatType -> ShowS
Show)
instance ToJSON ChatType where
toJSON :: ChatType -> Value
toJSON = ChatType -> Value
forall a (d :: Meta) (f :: * -> *).
(Generic a, GToJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
a -> Value
gtoJSON
instance FromJSON ChatType where
parseJSON :: Value -> Parser ChatType
parseJSON = Value -> Parser ChatType
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
data Message = Message
{ Message -> MessageId
messageMessageId :: MessageId
, Message -> Maybe User
messageFrom :: Maybe User
, Message -> Maybe Chat
messageSenderChat :: Maybe Chat
, Message -> POSIXTime
messageDate :: POSIXTime
, Message -> Chat
messageChat :: Chat
, Message -> Maybe User
messageForwardFrom :: Maybe User
, Message -> Maybe Chat
messageForwardFromChat :: Maybe Chat
, Message -> Maybe MessageId
messageForwardFromMessageId :: Maybe MessageId
, Message -> Maybe Text
messageForwardSignature :: Maybe Text
, Message -> Maybe Text
messageForwardSenderName :: Maybe Text
, Message -> Maybe POSIXTime
messageForwardDate :: Maybe POSIXTime
, Message -> Maybe Bool
messageIsAutomaticForward :: Maybe Bool
, Message -> Maybe Message
messageReplyToMessage :: Maybe Message
, Message -> Maybe User
messageViaBot :: Maybe User
, Message -> Maybe POSIXTime
messageEditDate :: Maybe POSIXTime
, Message -> Maybe Bool
messageHasProtectedContent :: Maybe Bool
, Message -> Maybe MediaGroupId
messageMediaGroupId :: Maybe MediaGroupId
, Message -> Maybe Text
messageAuthorSignature :: Maybe Text
, Message -> Maybe Text
messageText :: Maybe Text
, Message -> Maybe [MessageEntity]
messageEntities :: Maybe [MessageEntity]
, Message -> Maybe Animation
messageAnimation :: Maybe Animation
, Message -> Maybe Audio
messageAudio :: Maybe Audio
, Message -> Maybe Document
messageDocument :: Maybe Document
, Message -> Maybe [PhotoSize]
messagePhoto :: Maybe [PhotoSize]
, Message -> Maybe Sticker
messageSticker :: Maybe Sticker
, Message -> Maybe Video
messageVideo :: Maybe Video
, Message -> Maybe VideoNote
messageVideoNote :: Maybe VideoNote
, Message -> Maybe Voice
messageVoice :: Maybe Voice
, Message -> Maybe Text
messageCaption :: Maybe Text
, Message -> Maybe [MessageEntity]
messageCaptionEntities :: Maybe [MessageEntity]
, Message -> Maybe Contact
messageContact :: Maybe Contact
, Message -> Maybe Dice
messageDice :: Maybe Dice
, Message -> Maybe Game
messageGame :: Maybe Game
, Message -> Maybe Poll
messagePoll :: Maybe Poll
, Message -> Maybe Venue
messageVenue :: Maybe Venue
, Message -> Maybe Location
messageLocation :: Maybe Location
, Message -> Maybe [User]
messageNewChatMembers :: Maybe [User]
, Message -> Maybe User
messageLeftChatMember :: Maybe User
, Message -> Maybe Text
messageNewChatTitle :: Maybe Text
, Message -> Maybe [PhotoSize]
messageNewChatPhoto :: Maybe [PhotoSize]
, Message -> Maybe Bool
messageDeleteChatPhoto :: Maybe Bool
, Message -> Maybe Bool
messageGroupChatCreated :: Maybe Bool
, Message -> Maybe Bool
messageSupergroupChatCreated :: Maybe Bool
, Message -> Maybe Bool
messageChannelChatCreated :: Maybe Bool
, Message -> Maybe MessageAutoDeleteTimerChanged
messageAutoDeleteTimerChanged :: Maybe MessageAutoDeleteTimerChanged
, Message -> Maybe ChatId
messageMigrateToChatId :: Maybe ChatId
, Message -> Maybe ChatId
messageMigrateFromChatId :: Maybe ChatId
, Message -> Maybe Message
messagePinnedMessage :: Maybe Message
, Message -> Maybe Invoice
messageInvoice :: Maybe Invoice
, Message -> Maybe SuccessfulPayment
messageSuccessfulPayment :: Maybe SuccessfulPayment
, Message -> Maybe Text
messageConnectedWebsite :: Maybe Text
, Message -> Maybe PassportData
messagePassportData :: Maybe PassportData
, Message -> Maybe ProximityAlertTriggered
messageProximityAlertTriggered :: Maybe ProximityAlertTriggered
, Message -> Maybe VideoChatScheduled
messageVideoChatScheduled :: Maybe VideoChatScheduled
, Message -> Maybe VideoChatStarted
messageVideoChatStarted :: Maybe VideoChatStarted
, Message -> Maybe VideoChatEnded
messageVideoChatEnded :: Maybe VideoChatEnded
, Message -> Maybe VideoChatParticipantsInvited
messageVideoChatParticipantsInvited :: Maybe VideoChatParticipantsInvited
, Message -> Maybe WebAppData
messageWebAppData :: Maybe WebAppData
, Message -> Maybe InlineKeyboardMarkup
messageReplyMarkup :: Maybe InlineKeyboardMarkup
}
deriving ((forall x. Message -> Rep Message x)
-> (forall x. Rep Message x -> Message) -> Generic Message
forall x. Rep Message x -> Message
forall x. Message -> Rep Message x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Message x -> Message
$cfrom :: forall x. Message -> Rep Message x
Generic, Int -> Message -> ShowS
[Message] -> ShowS
Message -> String
(Int -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Message] -> ShowS
$cshowList :: [Message] -> ShowS
show :: Message -> String
$cshow :: Message -> String
showsPrec :: Int -> Message -> ShowS
$cshowsPrec :: Int -> Message -> ShowS
Show)
newtype MessageId = MessageId Integer
deriving (MessageId -> MessageId -> Bool
(MessageId -> MessageId -> Bool)
-> (MessageId -> MessageId -> Bool) -> Eq MessageId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageId -> MessageId -> Bool
$c/= :: MessageId -> MessageId -> Bool
== :: MessageId -> MessageId -> Bool
$c== :: MessageId -> MessageId -> Bool
Eq, Int -> MessageId -> ShowS
[MessageId] -> ShowS
MessageId -> String
(Int -> MessageId -> ShowS)
-> (MessageId -> String)
-> ([MessageId] -> ShowS)
-> Show MessageId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageId] -> ShowS
$cshowList :: [MessageId] -> ShowS
show :: MessageId -> String
$cshow :: MessageId -> String
showsPrec :: Int -> MessageId -> ShowS
$cshowsPrec :: Int -> MessageId -> ShowS
Show, [MessageId] -> Encoding
[MessageId] -> Value
MessageId -> Encoding
MessageId -> Value
(MessageId -> Value)
-> (MessageId -> Encoding)
-> ([MessageId] -> Value)
-> ([MessageId] -> Encoding)
-> ToJSON MessageId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MessageId] -> Encoding
$ctoEncodingList :: [MessageId] -> Encoding
toJSONList :: [MessageId] -> Value
$ctoJSONList :: [MessageId] -> Value
toEncoding :: MessageId -> Encoding
$ctoEncoding :: MessageId -> Encoding
toJSON :: MessageId -> Value
$ctoJSON :: MessageId -> Value
ToJSON, Value -> Parser [MessageId]
Value -> Parser MessageId
(Value -> Parser MessageId)
-> (Value -> Parser [MessageId]) -> FromJSON MessageId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MessageId]
$cparseJSONList :: Value -> Parser [MessageId]
parseJSON :: Value -> Parser MessageId
$cparseJSON :: Value -> Parser MessageId
FromJSON, Eq MessageId
Eq MessageId
-> (Int -> MessageId -> Int)
-> (MessageId -> Int)
-> Hashable MessageId
Int -> MessageId -> Int
MessageId -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: MessageId -> Int
$chash :: MessageId -> Int
hashWithSalt :: Int -> MessageId -> Int
$chashWithSalt :: Int -> MessageId -> Int
$cp1Hashable :: Eq MessageId
Hashable)
instance ToHttpApiData MessageId where
toUrlPiece :: MessageId -> Text
toUrlPiece MessageId
a = String -> Text
pack (String -> Text) -> (Integer -> String) -> Integer -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Show Integer => Integer -> String
forall a. Show a => a -> String
show @Integer (Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ MessageId -> Integer
coerce MessageId
a
newtype MediaGroupId = MediaGroupId Text
deriving (MediaGroupId -> MediaGroupId -> Bool
(MediaGroupId -> MediaGroupId -> Bool)
-> (MediaGroupId -> MediaGroupId -> Bool) -> Eq MediaGroupId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MediaGroupId -> MediaGroupId -> Bool
$c/= :: MediaGroupId -> MediaGroupId -> Bool
== :: MediaGroupId -> MediaGroupId -> Bool
$c== :: MediaGroupId -> MediaGroupId -> Bool
Eq, Int -> MediaGroupId -> ShowS
[MediaGroupId] -> ShowS
MediaGroupId -> String
(Int -> MediaGroupId -> ShowS)
-> (MediaGroupId -> String)
-> ([MediaGroupId] -> ShowS)
-> Show MediaGroupId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MediaGroupId] -> ShowS
$cshowList :: [MediaGroupId] -> ShowS
show :: MediaGroupId -> String
$cshow :: MediaGroupId -> String
showsPrec :: Int -> MediaGroupId -> ShowS
$cshowsPrec :: Int -> MediaGroupId -> ShowS
Show, [MediaGroupId] -> Encoding
[MediaGroupId] -> Value
MediaGroupId -> Encoding
MediaGroupId -> Value
(MediaGroupId -> Value)
-> (MediaGroupId -> Encoding)
-> ([MediaGroupId] -> Value)
-> ([MediaGroupId] -> Encoding)
-> ToJSON MediaGroupId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MediaGroupId] -> Encoding
$ctoEncodingList :: [MediaGroupId] -> Encoding
toJSONList :: [MediaGroupId] -> Value
$ctoJSONList :: [MediaGroupId] -> Value
toEncoding :: MediaGroupId -> Encoding
$ctoEncoding :: MediaGroupId -> Encoding
toJSON :: MediaGroupId -> Value
$ctoJSON :: MediaGroupId -> Value
ToJSON, Value -> Parser [MediaGroupId]
Value -> Parser MediaGroupId
(Value -> Parser MediaGroupId)
-> (Value -> Parser [MediaGroupId]) -> FromJSON MediaGroupId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MediaGroupId]
$cparseJSONList :: Value -> Parser [MediaGroupId]
parseJSON :: Value -> Parser MediaGroupId
$cparseJSON :: Value -> Parser MediaGroupId
FromJSON)
data MessageEntity = MessageEntity
{ MessageEntity -> MessageEntityType
messageEntityType :: MessageEntityType
, MessageEntity -> Int
messageEntityOffset :: Int
, MessageEntity -> Int
messageEntityLength :: Int
, MessageEntity -> Maybe Text
messageEntityUrl :: Maybe Text
, MessageEntity -> Maybe User
messageEntityUser :: Maybe User
, MessageEntity -> Maybe Text
messageEntityLanguage :: Maybe Text
}
deriving ((forall x. MessageEntity -> Rep MessageEntity x)
-> (forall x. Rep MessageEntity x -> MessageEntity)
-> Generic MessageEntity
forall x. Rep MessageEntity x -> MessageEntity
forall x. MessageEntity -> Rep MessageEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageEntity x -> MessageEntity
$cfrom :: forall x. MessageEntity -> Rep MessageEntity x
Generic, Int -> MessageEntity -> ShowS
[MessageEntity] -> ShowS
MessageEntity -> String
(Int -> MessageEntity -> ShowS)
-> (MessageEntity -> String)
-> ([MessageEntity] -> ShowS)
-> Show MessageEntity
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageEntity] -> ShowS
$cshowList :: [MessageEntity] -> ShowS
show :: MessageEntity -> String
$cshow :: MessageEntity -> String
showsPrec :: Int -> MessageEntity -> ShowS
$cshowsPrec :: Int -> MessageEntity -> ShowS
Show)
data MessageEntityType
= MessageEntityMention
| MessageEntityHashtag
| MessageEntityBotCommand
| MessageEntityUrl
| MessageEntityEmail
| MessageEntityBold
| MessageEntityItalic
| MessageEntityUnderline
| MessageEntityStrikethrough
| MessageEntityCode
| MessageEntityPre
| MessageEntityTextLink
| MessageEntityTextMention
| MessageEntityCashtag
| MessageEntityPhoneNumber
| MessageEntitySpoiler
deriving (MessageEntityType -> MessageEntityType -> Bool
(MessageEntityType -> MessageEntityType -> Bool)
-> (MessageEntityType -> MessageEntityType -> Bool)
-> Eq MessageEntityType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageEntityType -> MessageEntityType -> Bool
$c/= :: MessageEntityType -> MessageEntityType -> Bool
== :: MessageEntityType -> MessageEntityType -> Bool
$c== :: MessageEntityType -> MessageEntityType -> Bool
Eq, Int -> MessageEntityType -> ShowS
[MessageEntityType] -> ShowS
MessageEntityType -> String
(Int -> MessageEntityType -> ShowS)
-> (MessageEntityType -> String)
-> ([MessageEntityType] -> ShowS)
-> Show MessageEntityType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageEntityType] -> ShowS
$cshowList :: [MessageEntityType] -> ShowS
show :: MessageEntityType -> String
$cshow :: MessageEntityType -> String
showsPrec :: Int -> MessageEntityType -> ShowS
$cshowsPrec :: Int -> MessageEntityType -> ShowS
Show, (forall x. MessageEntityType -> Rep MessageEntityType x)
-> (forall x. Rep MessageEntityType x -> MessageEntityType)
-> Generic MessageEntityType
forall x. Rep MessageEntityType x -> MessageEntityType
forall x. MessageEntityType -> Rep MessageEntityType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageEntityType x -> MessageEntityType
$cfrom :: forall x. MessageEntityType -> Rep MessageEntityType x
Generic)
data PhotoSize = PhotoSize
{ PhotoSize -> FileId
photoSizeFileId :: FileId
, PhotoSize -> FileId
photoSizeFileUniqueId :: FileId
, PhotoSize -> Int
photoSizeWidth :: Int
, PhotoSize -> Int
photoSizeHeight :: Int
, PhotoSize -> Maybe Int
photoSizeFileSize :: Maybe Int
}
deriving ((forall x. PhotoSize -> Rep PhotoSize x)
-> (forall x. Rep PhotoSize x -> PhotoSize) -> Generic PhotoSize
forall x. Rep PhotoSize x -> PhotoSize
forall x. PhotoSize -> Rep PhotoSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PhotoSize x -> PhotoSize
$cfrom :: forall x. PhotoSize -> Rep PhotoSize x
Generic, Int -> PhotoSize -> ShowS
[PhotoSize] -> ShowS
PhotoSize -> String
(Int -> PhotoSize -> ShowS)
-> (PhotoSize -> String)
-> ([PhotoSize] -> ShowS)
-> Show PhotoSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PhotoSize] -> ShowS
$cshowList :: [PhotoSize] -> ShowS
show :: PhotoSize -> String
$cshow :: PhotoSize -> String
showsPrec :: Int -> PhotoSize -> ShowS
$cshowsPrec :: Int -> PhotoSize -> ShowS
Show)
newtype FileId = FileId Text
deriving (FileId -> FileId -> Bool
(FileId -> FileId -> Bool)
-> (FileId -> FileId -> Bool) -> Eq FileId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileId -> FileId -> Bool
$c/= :: FileId -> FileId -> Bool
== :: FileId -> FileId -> Bool
$c== :: FileId -> FileId -> Bool
Eq, Int -> FileId -> ShowS
[FileId] -> ShowS
FileId -> String
(Int -> FileId -> ShowS)
-> (FileId -> String) -> ([FileId] -> ShowS) -> Show FileId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileId] -> ShowS
$cshowList :: [FileId] -> ShowS
show :: FileId -> String
$cshow :: FileId -> String
showsPrec :: Int -> FileId -> ShowS
$cshowsPrec :: Int -> FileId -> ShowS
Show, [FileId] -> Encoding
[FileId] -> Value
FileId -> Encoding
FileId -> Value
(FileId -> Value)
-> (FileId -> Encoding)
-> ([FileId] -> Value)
-> ([FileId] -> Encoding)
-> ToJSON FileId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FileId] -> Encoding
$ctoEncodingList :: [FileId] -> Encoding
toJSONList :: [FileId] -> Value
$ctoJSONList :: [FileId] -> Value
toEncoding :: FileId -> Encoding
$ctoEncoding :: FileId -> Encoding
toJSON :: FileId -> Value
$ctoJSON :: FileId -> Value
ToJSON, Value -> Parser [FileId]
Value -> Parser FileId
(Value -> Parser FileId)
-> (Value -> Parser [FileId]) -> FromJSON FileId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FileId]
$cparseJSONList :: Value -> Parser [FileId]
parseJSON :: Value -> Parser FileId
$cparseJSON :: Value -> Parser FileId
FromJSON)
instance ToHttpApiData FileId where
toUrlPiece :: FileId -> Text
toUrlPiece = FileId -> Text
coerce
data Animation = Animation
{ Animation -> FileId
animationFileId :: FileId
, Animation -> FileId
animationFileUniqueId :: FileId
, Animation -> Int
animationWidth :: Int
, Animation -> Int
animationHeight :: Int
, Animation -> Seconds
animationDuration :: Seconds
, Animation -> Maybe PhotoSize
animationThumb :: Maybe PhotoSize
, Animation -> Maybe Text
animationFileName :: Maybe Text
, Animation -> Maybe Text
animationMimeType :: Maybe Text
, Animation -> Maybe Int
animationFileSize :: Maybe Int
}
deriving ((forall x. Animation -> Rep Animation x)
-> (forall x. Rep Animation x -> Animation) -> Generic Animation
forall x. Rep Animation x -> Animation
forall x. Animation -> Rep Animation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Animation x -> Animation
$cfrom :: forall x. Animation -> Rep Animation x
Generic, Int -> Animation -> ShowS
[Animation] -> ShowS
Animation -> String
(Int -> Animation -> ShowS)
-> (Animation -> String)
-> ([Animation] -> ShowS)
-> Show Animation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Animation] -> ShowS
$cshowList :: [Animation] -> ShowS
show :: Animation -> String
$cshow :: Animation -> String
showsPrec :: Int -> Animation -> ShowS
$cshowsPrec :: Int -> Animation -> ShowS
Show)
data Audio = Audio
{ Audio -> FileId
audioFileId :: FileId
, Audio -> FileId
audioFileUniqueId :: FileId
, Audio -> Seconds
audioDuration :: Seconds
, Audio -> Maybe Text
audioPerformer :: Maybe Text
, Audio -> Maybe Text
audioTitle :: Maybe Text
, Audio -> Maybe Text
audioFileName :: Maybe Text
, Audio -> Maybe Text
audioMimeType :: Maybe Text
, Audio -> Maybe Int
audioFileSize :: Maybe Int
, Audio -> Maybe PhotoSize
audioThumb :: Maybe PhotoSize
}
deriving ((forall x. Audio -> Rep Audio x)
-> (forall x. Rep Audio x -> Audio) -> Generic Audio
forall x. Rep Audio x -> Audio
forall x. Audio -> Rep Audio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Audio x -> Audio
$cfrom :: forall x. Audio -> Rep Audio x
Generic, Int -> Audio -> ShowS
[Audio] -> ShowS
Audio -> String
(Int -> Audio -> ShowS)
-> (Audio -> String) -> ([Audio] -> ShowS) -> Show Audio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Audio] -> ShowS
$cshowList :: [Audio] -> ShowS
show :: Audio -> String
$cshow :: Audio -> String
showsPrec :: Int -> Audio -> ShowS
$cshowsPrec :: Int -> Audio -> ShowS
Show)
data Document = Document
{ Document -> FileId
documentFileId :: FileId
, Document -> FileId
documentFileUniqueId :: FileId
, Document -> Maybe PhotoSize
documentThumb :: Maybe PhotoSize
, Document -> Maybe Text
documentFileName :: Maybe Text
, Document -> Maybe Text
documentMimeType :: Maybe Text
, Document -> Maybe Int
documentFileSize :: Maybe Int
}
deriving ((forall x. Document -> Rep Document x)
-> (forall x. Rep Document x -> Document) -> Generic Document
forall x. Rep Document x -> Document
forall x. Document -> Rep Document x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Document x -> Document
$cfrom :: forall x. Document -> Rep Document x
Generic, Int -> Document -> ShowS
[Document] -> ShowS
Document -> String
(Int -> Document -> ShowS)
-> (Document -> String) -> ([Document] -> ShowS) -> Show Document
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Document] -> ShowS
$cshowList :: [Document] -> ShowS
show :: Document -> String
$cshow :: Document -> String
showsPrec :: Int -> Document -> ShowS
$cshowsPrec :: Int -> Document -> ShowS
Show)
data Video = Video
{ Video -> FileId
videoFileId :: FileId
, Video -> FileId
videoFileUniqueId :: FileId
, Video -> Int
videoWidth :: Int
, Video -> Int
videoHeight :: Int
, Video -> Seconds
videoDuration :: Seconds
, Video -> Maybe PhotoSize
videoThumb :: Maybe PhotoSize
, Video -> Maybe Text
videoFileName :: Maybe Text
, Video -> Maybe Text
videoMimeType :: Maybe Text
, Video -> Maybe Int
videoFileSize :: Maybe Int
}
deriving ((forall x. Video -> Rep Video x)
-> (forall x. Rep Video x -> Video) -> Generic Video
forall x. Rep Video x -> Video
forall x. Video -> Rep Video x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Video x -> Video
$cfrom :: forall x. Video -> Rep Video x
Generic, Int -> Video -> ShowS
[Video] -> ShowS
Video -> String
(Int -> Video -> ShowS)
-> (Video -> String) -> ([Video] -> ShowS) -> Show Video
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Video] -> ShowS
$cshowList :: [Video] -> ShowS
show :: Video -> String
$cshow :: Video -> String
showsPrec :: Int -> Video -> ShowS
$cshowsPrec :: Int -> Video -> ShowS
Show)
data VideoNote = VideoNote
{ VideoNote -> FileId
videoNoteFileId :: FileId
, VideoNote -> FileId
videoNoteFileUniqueId :: FileId
, VideoNote -> Int
videoNoteLength :: Int
, VideoNote -> Seconds
videoNoteDuration :: Seconds
, VideoNote -> Maybe PhotoSize
videoNoteThumb :: Maybe PhotoSize
, VideoNote -> Maybe Int
videoNoteFileSize :: Maybe Int
}
deriving ((forall x. VideoNote -> Rep VideoNote x)
-> (forall x. Rep VideoNote x -> VideoNote) -> Generic VideoNote
forall x. Rep VideoNote x -> VideoNote
forall x. VideoNote -> Rep VideoNote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VideoNote x -> VideoNote
$cfrom :: forall x. VideoNote -> Rep VideoNote x
Generic, Int -> VideoNote -> ShowS
[VideoNote] -> ShowS
VideoNote -> String
(Int -> VideoNote -> ShowS)
-> (VideoNote -> String)
-> ([VideoNote] -> ShowS)
-> Show VideoNote
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoNote] -> ShowS
$cshowList :: [VideoNote] -> ShowS
show :: VideoNote -> String
$cshow :: VideoNote -> String
showsPrec :: Int -> VideoNote -> ShowS
$cshowsPrec :: Int -> VideoNote -> ShowS
Show)
data Voice = Voice
{ Voice -> FileId
voiceFileId :: FileId
, Voice -> FileId
voiceFileUniqueId :: FileId
, Voice -> Seconds
voiceDuration :: Seconds
, Voice -> Maybe Text
voiceMimeType :: Maybe Text
, Voice -> Maybe Int
voiceFileSize :: Maybe Int
}
deriving ((forall x. Voice -> Rep Voice x)
-> (forall x. Rep Voice x -> Voice) -> Generic Voice
forall x. Rep Voice x -> Voice
forall x. Voice -> Rep Voice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Voice x -> Voice
$cfrom :: forall x. Voice -> Rep Voice x
Generic, Int -> Voice -> ShowS
[Voice] -> ShowS
Voice -> String
(Int -> Voice -> ShowS)
-> (Voice -> String) -> ([Voice] -> ShowS) -> Show Voice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Voice] -> ShowS
$cshowList :: [Voice] -> ShowS
show :: Voice -> String
$cshow :: Voice -> String
showsPrec :: Int -> Voice -> ShowS
$cshowsPrec :: Int -> Voice -> ShowS
Show)
data Contact = Contact
{ Contact -> Text
contactPhoneNumber :: Text
, Contact -> Text
contactFirstName :: Text
, Contact -> Maybe Text
contactLastName :: Maybe Text
, Contact -> Maybe UserId
contactUserId :: Maybe UserId
, Contact -> Maybe Text
contactVcard :: Maybe Text
}
deriving ((forall x. Contact -> Rep Contact x)
-> (forall x. Rep Contact x -> Contact) -> Generic Contact
forall x. Rep Contact x -> Contact
forall x. Contact -> Rep Contact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Contact x -> Contact
$cfrom :: forall x. Contact -> Rep Contact x
Generic, Int -> Contact -> ShowS
[Contact] -> ShowS
Contact -> String
(Int -> Contact -> ShowS)
-> (Contact -> String) -> ([Contact] -> ShowS) -> Show Contact
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Contact] -> ShowS
$cshowList :: [Contact] -> ShowS
show :: Contact -> String
$cshow :: Contact -> String
showsPrec :: Int -> Contact -> ShowS
$cshowsPrec :: Int -> Contact -> ShowS
Show)
data Dice = Dice
{ Dice -> Text
diceEmoji :: Text
, Dice -> Int
diceValue :: Int
}
deriving ((forall x. Dice -> Rep Dice x)
-> (forall x. Rep Dice x -> Dice) -> Generic Dice
forall x. Rep Dice x -> Dice
forall x. Dice -> Rep Dice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Dice x -> Dice
$cfrom :: forall x. Dice -> Rep Dice x
Generic, Int -> Dice -> ShowS
[Dice] -> ShowS
Dice -> String
(Int -> Dice -> ShowS)
-> (Dice -> String) -> ([Dice] -> ShowS) -> Show Dice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Dice] -> ShowS
$cshowList :: [Dice] -> ShowS
show :: Dice -> String
$cshow :: Dice -> String
showsPrec :: Int -> Dice -> ShowS
$cshowsPrec :: Int -> Dice -> ShowS
Show)
data PollOption = PollOption
{ PollOption -> Text
pollOptionText :: Text
, PollOption -> Int
pollOptionVoterCount :: Int
}
deriving ((forall x. PollOption -> Rep PollOption x)
-> (forall x. Rep PollOption x -> PollOption) -> Generic PollOption
forall x. Rep PollOption x -> PollOption
forall x. PollOption -> Rep PollOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollOption x -> PollOption
$cfrom :: forall x. PollOption -> Rep PollOption x
Generic, Int -> PollOption -> ShowS
[PollOption] -> ShowS
PollOption -> String
(Int -> PollOption -> ShowS)
-> (PollOption -> String)
-> ([PollOption] -> ShowS)
-> Show PollOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollOption] -> ShowS
$cshowList :: [PollOption] -> ShowS
show :: PollOption -> String
$cshow :: PollOption -> String
showsPrec :: Int -> PollOption -> ShowS
$cshowsPrec :: Int -> PollOption -> ShowS
Show)
data PollAnswer = PollAnswer
{ PollAnswer -> PollId
pollAnswerPollId :: PollId
, PollAnswer -> User
pollAnswerUser :: User
, PollAnswer -> [Int]
pollAnswerOptionIds :: [Int]
}
deriving ((forall x. PollAnswer -> Rep PollAnswer x)
-> (forall x. Rep PollAnswer x -> PollAnswer) -> Generic PollAnswer
forall x. Rep PollAnswer x -> PollAnswer
forall x. PollAnswer -> Rep PollAnswer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollAnswer x -> PollAnswer
$cfrom :: forall x. PollAnswer -> Rep PollAnswer x
Generic, Int -> PollAnswer -> ShowS
[PollAnswer] -> ShowS
PollAnswer -> String
(Int -> PollAnswer -> ShowS)
-> (PollAnswer -> String)
-> ([PollAnswer] -> ShowS)
-> Show PollAnswer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollAnswer] -> ShowS
$cshowList :: [PollAnswer] -> ShowS
show :: PollAnswer -> String
$cshow :: PollAnswer -> String
showsPrec :: Int -> PollAnswer -> ShowS
$cshowsPrec :: Int -> PollAnswer -> ShowS
Show)
newtype PollId = PollId Text
deriving (PollId -> PollId -> Bool
(PollId -> PollId -> Bool)
-> (PollId -> PollId -> Bool) -> Eq PollId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollId -> PollId -> Bool
$c/= :: PollId -> PollId -> Bool
== :: PollId -> PollId -> Bool
$c== :: PollId -> PollId -> Bool
Eq, Int -> PollId -> ShowS
[PollId] -> ShowS
PollId -> String
(Int -> PollId -> ShowS)
-> (PollId -> String) -> ([PollId] -> ShowS) -> Show PollId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollId] -> ShowS
$cshowList :: [PollId] -> ShowS
show :: PollId -> String
$cshow :: PollId -> String
showsPrec :: Int -> PollId -> ShowS
$cshowsPrec :: Int -> PollId -> ShowS
Show, [PollId] -> Encoding
[PollId] -> Value
PollId -> Encoding
PollId -> Value
(PollId -> Value)
-> (PollId -> Encoding)
-> ([PollId] -> Value)
-> ([PollId] -> Encoding)
-> ToJSON PollId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [PollId] -> Encoding
$ctoEncodingList :: [PollId] -> Encoding
toJSONList :: [PollId] -> Value
$ctoJSONList :: [PollId] -> Value
toEncoding :: PollId -> Encoding
$ctoEncoding :: PollId -> Encoding
toJSON :: PollId -> Value
$ctoJSON :: PollId -> Value
ToJSON, Value -> Parser [PollId]
Value -> Parser PollId
(Value -> Parser PollId)
-> (Value -> Parser [PollId]) -> FromJSON PollId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [PollId]
$cparseJSONList :: Value -> Parser [PollId]
parseJSON :: Value -> Parser PollId
$cparseJSON :: Value -> Parser PollId
FromJSON)
data Poll = Poll
{ Poll -> PollId
pollId :: PollId
, Poll -> Text
pollQuestion :: Text
, Poll -> [PollOption]
pollOptions :: [PollOption]
, Poll -> Int
pollTotalVoterCount :: Int
, Poll -> Bool
pollIsClosed :: Bool
, Poll -> Bool
pollIsAnonymous :: Bool
, Poll -> PollType
pollType :: PollType
, Poll -> Bool
pollAllowsMultipleAnswers :: Bool
, Poll -> Maybe Int
pollCorrectOptionId :: Maybe Int
, Poll -> Maybe Text
pollExplanation :: Maybe Text
, Poll -> Maybe [MessageEntity]
pollExplanationEntities :: Maybe [MessageEntity]
, Poll -> Maybe Seconds
pollOpenPeriod :: Maybe Seconds
, Poll -> Maybe POSIXTime
pollCloseData :: Maybe POSIXTime
}
deriving ((forall x. Poll -> Rep Poll x)
-> (forall x. Rep Poll x -> Poll) -> Generic Poll
forall x. Rep Poll x -> Poll
forall x. Poll -> Rep Poll x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Poll x -> Poll
$cfrom :: forall x. Poll -> Rep Poll x
Generic, Int -> Poll -> ShowS
[Poll] -> ShowS
Poll -> String
(Int -> Poll -> ShowS)
-> (Poll -> String) -> ([Poll] -> ShowS) -> Show Poll
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Poll] -> ShowS
$cshowList :: [Poll] -> ShowS
show :: Poll -> String
$cshow :: Poll -> String
showsPrec :: Int -> Poll -> ShowS
$cshowsPrec :: Int -> Poll -> ShowS
Show)
data Location = Location
{ Location -> Float
locationLongitude :: Float
, Location -> Float
locationLatitude :: Float
, Location -> Maybe Float
locationHorizontalAccuracy :: Maybe Float
, Location -> Maybe Seconds
locationLivePeriod :: Maybe Seconds
, Location -> Maybe Int
locationHeading :: Maybe Int
, Location -> Maybe Int
locationProximityAlertRadius :: Maybe Int
}
deriving ((forall x. Location -> Rep Location x)
-> (forall x. Rep Location x -> Location) -> Generic Location
forall x. Rep Location x -> Location
forall x. Location -> Rep Location x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Location x -> Location
$cfrom :: forall x. Location -> Rep Location x
Generic, Int -> Location -> ShowS
[Location] -> ShowS
Location -> String
(Int -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Location] -> ShowS
$cshowList :: [Location] -> ShowS
show :: Location -> String
$cshow :: Location -> String
showsPrec :: Int -> Location -> ShowS
$cshowsPrec :: Int -> Location -> ShowS
Show)
data Venue = Venue
{ Venue -> Location
venueLocation :: Location
, Venue -> Text
venueTitle :: Text
, Venue -> Text
venueAddress :: Text
, Venue -> Maybe Text
venueFoursquareId :: Maybe Text
, Venue -> Maybe Text
venueFoursquareType :: Maybe Text
, Venue -> Maybe Text
venueGooglePlaceId :: Maybe Text
, Venue -> Maybe Text
venueGooglePlaceType :: Maybe Text
}
deriving ((forall x. Venue -> Rep Venue x)
-> (forall x. Rep Venue x -> Venue) -> Generic Venue
forall x. Rep Venue x -> Venue
forall x. Venue -> Rep Venue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Venue x -> Venue
$cfrom :: forall x. Venue -> Rep Venue x
Generic, Int -> Venue -> ShowS
[Venue] -> ShowS
Venue -> String
(Int -> Venue -> ShowS)
-> (Venue -> String) -> ([Venue] -> ShowS) -> Show Venue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Venue] -> ShowS
$cshowList :: [Venue] -> ShowS
show :: Venue -> String
$cshow :: Venue -> String
showsPrec :: Int -> Venue -> ShowS
$cshowsPrec :: Int -> Venue -> ShowS
Show)
data ProximityAlertTriggered = ProximityAlertTriggered
{ ProximityAlertTriggered -> User
proximityAlertTriggeredTraveler :: User
, ProximityAlertTriggered -> User
proximityAlertTriggeredWatcher :: User
, ProximityAlertTriggered -> Int
proximityAlertTriggeredDistance :: Int
}
deriving ((forall x.
ProximityAlertTriggered -> Rep ProximityAlertTriggered x)
-> (forall x.
Rep ProximityAlertTriggered x -> ProximityAlertTriggered)
-> Generic ProximityAlertTriggered
forall x. Rep ProximityAlertTriggered x -> ProximityAlertTriggered
forall x. ProximityAlertTriggered -> Rep ProximityAlertTriggered x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProximityAlertTriggered x -> ProximityAlertTriggered
$cfrom :: forall x. ProximityAlertTriggered -> Rep ProximityAlertTriggered x
Generic, Int -> ProximityAlertTriggered -> ShowS
[ProximityAlertTriggered] -> ShowS
ProximityAlertTriggered -> String
(Int -> ProximityAlertTriggered -> ShowS)
-> (ProximityAlertTriggered -> String)
-> ([ProximityAlertTriggered] -> ShowS)
-> Show ProximityAlertTriggered
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProximityAlertTriggered] -> ShowS
$cshowList :: [ProximityAlertTriggered] -> ShowS
show :: ProximityAlertTriggered -> String
$cshow :: ProximityAlertTriggered -> String
showsPrec :: Int -> ProximityAlertTriggered -> ShowS
$cshowsPrec :: Int -> ProximityAlertTriggered -> ShowS
Show)
data MessageAutoDeleteTimerChanged = MessageAutoDeleteTimerChanged
{ MessageAutoDeleteTimerChanged -> Seconds
messageAutoDeleteTimerChangedMessageAutoDeleteTime :: Seconds
}
deriving ((forall x.
MessageAutoDeleteTimerChanged
-> Rep MessageAutoDeleteTimerChanged x)
-> (forall x.
Rep MessageAutoDeleteTimerChanged x
-> MessageAutoDeleteTimerChanged)
-> Generic MessageAutoDeleteTimerChanged
forall x.
Rep MessageAutoDeleteTimerChanged x
-> MessageAutoDeleteTimerChanged
forall x.
MessageAutoDeleteTimerChanged
-> Rep MessageAutoDeleteTimerChanged x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep MessageAutoDeleteTimerChanged x
-> MessageAutoDeleteTimerChanged
$cfrom :: forall x.
MessageAutoDeleteTimerChanged
-> Rep MessageAutoDeleteTimerChanged x
Generic, Int -> MessageAutoDeleteTimerChanged -> ShowS
[MessageAutoDeleteTimerChanged] -> ShowS
MessageAutoDeleteTimerChanged -> String
(Int -> MessageAutoDeleteTimerChanged -> ShowS)
-> (MessageAutoDeleteTimerChanged -> String)
-> ([MessageAutoDeleteTimerChanged] -> ShowS)
-> Show MessageAutoDeleteTimerChanged
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageAutoDeleteTimerChanged] -> ShowS
$cshowList :: [MessageAutoDeleteTimerChanged] -> ShowS
show :: MessageAutoDeleteTimerChanged -> String
$cshow :: MessageAutoDeleteTimerChanged -> String
showsPrec :: Int -> MessageAutoDeleteTimerChanged -> ShowS
$cshowsPrec :: Int -> MessageAutoDeleteTimerChanged -> ShowS
Show)
data VideoChatScheduled = VideoChatScheduled
{ VideoChatScheduled -> POSIXTime
videoChatScheduledStartDate :: POSIXTime
}
deriving ((forall x. VideoChatScheduled -> Rep VideoChatScheduled x)
-> (forall x. Rep VideoChatScheduled x -> VideoChatScheduled)
-> Generic VideoChatScheduled
forall x. Rep VideoChatScheduled x -> VideoChatScheduled
forall x. VideoChatScheduled -> Rep VideoChatScheduled x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VideoChatScheduled x -> VideoChatScheduled
$cfrom :: forall x. VideoChatScheduled -> Rep VideoChatScheduled x
Generic, Int -> VideoChatScheduled -> ShowS
[VideoChatScheduled] -> ShowS
VideoChatScheduled -> String
(Int -> VideoChatScheduled -> ShowS)
-> (VideoChatScheduled -> String)
-> ([VideoChatScheduled] -> ShowS)
-> Show VideoChatScheduled
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoChatScheduled] -> ShowS
$cshowList :: [VideoChatScheduled] -> ShowS
show :: VideoChatScheduled -> String
$cshow :: VideoChatScheduled -> String
showsPrec :: Int -> VideoChatScheduled -> ShowS
$cshowsPrec :: Int -> VideoChatScheduled -> ShowS
Show)
data VideoChatStarted = VideoChatStarted
deriving ((forall x. VideoChatStarted -> Rep VideoChatStarted x)
-> (forall x. Rep VideoChatStarted x -> VideoChatStarted)
-> Generic VideoChatStarted
forall x. Rep VideoChatStarted x -> VideoChatStarted
forall x. VideoChatStarted -> Rep VideoChatStarted x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VideoChatStarted x -> VideoChatStarted
$cfrom :: forall x. VideoChatStarted -> Rep VideoChatStarted x
Generic, Int -> VideoChatStarted -> ShowS
[VideoChatStarted] -> ShowS
VideoChatStarted -> String
(Int -> VideoChatStarted -> ShowS)
-> (VideoChatStarted -> String)
-> ([VideoChatStarted] -> ShowS)
-> Show VideoChatStarted
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoChatStarted] -> ShowS
$cshowList :: [VideoChatStarted] -> ShowS
show :: VideoChatStarted -> String
$cshow :: VideoChatStarted -> String
showsPrec :: Int -> VideoChatStarted -> ShowS
$cshowsPrec :: Int -> VideoChatStarted -> ShowS
Show)
data VideoChatEnded = VideoChatEnded
{ VideoChatEnded -> Seconds
videoChatEndedDuration :: Seconds
}
deriving ((forall x. VideoChatEnded -> Rep VideoChatEnded x)
-> (forall x. Rep VideoChatEnded x -> VideoChatEnded)
-> Generic VideoChatEnded
forall x. Rep VideoChatEnded x -> VideoChatEnded
forall x. VideoChatEnded -> Rep VideoChatEnded x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VideoChatEnded x -> VideoChatEnded
$cfrom :: forall x. VideoChatEnded -> Rep VideoChatEnded x
Generic, Int -> VideoChatEnded -> ShowS
[VideoChatEnded] -> ShowS
VideoChatEnded -> String
(Int -> VideoChatEnded -> ShowS)
-> (VideoChatEnded -> String)
-> ([VideoChatEnded] -> ShowS)
-> Show VideoChatEnded
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoChatEnded] -> ShowS
$cshowList :: [VideoChatEnded] -> ShowS
show :: VideoChatEnded -> String
$cshow :: VideoChatEnded -> String
showsPrec :: Int -> VideoChatEnded -> ShowS
$cshowsPrec :: Int -> VideoChatEnded -> ShowS
Show)
data VideoChatParticipantsInvited = VideoChatParticipantsInvited
{ VideoChatParticipantsInvited -> Maybe [User]
videoChatParticipantsInvitedUsers :: Maybe [User]
}
deriving ((forall x.
VideoChatParticipantsInvited -> Rep VideoChatParticipantsInvited x)
-> (forall x.
Rep VideoChatParticipantsInvited x -> VideoChatParticipantsInvited)
-> Generic VideoChatParticipantsInvited
forall x.
Rep VideoChatParticipantsInvited x -> VideoChatParticipantsInvited
forall x.
VideoChatParticipantsInvited -> Rep VideoChatParticipantsInvited x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep VideoChatParticipantsInvited x -> VideoChatParticipantsInvited
$cfrom :: forall x.
VideoChatParticipantsInvited -> Rep VideoChatParticipantsInvited x
Generic, Int -> VideoChatParticipantsInvited -> ShowS
[VideoChatParticipantsInvited] -> ShowS
VideoChatParticipantsInvited -> String
(Int -> VideoChatParticipantsInvited -> ShowS)
-> (VideoChatParticipantsInvited -> String)
-> ([VideoChatParticipantsInvited] -> ShowS)
-> Show VideoChatParticipantsInvited
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoChatParticipantsInvited] -> ShowS
$cshowList :: [VideoChatParticipantsInvited] -> ShowS
show :: VideoChatParticipantsInvited -> String
$cshow :: VideoChatParticipantsInvited -> String
showsPrec :: Int -> VideoChatParticipantsInvited -> ShowS
$cshowsPrec :: Int -> VideoChatParticipantsInvited -> ShowS
Show)
data UserProfilePhotos = UserProfilePhotos
{ UserProfilePhotos -> Int
userProfilePhotosTotalCount :: Int
, UserProfilePhotos -> [[PhotoSize]]
userProfilePhotosPhotos :: [[PhotoSize]]
}
deriving ((forall x. UserProfilePhotos -> Rep UserProfilePhotos x)
-> (forall x. Rep UserProfilePhotos x -> UserProfilePhotos)
-> Generic UserProfilePhotos
forall x. Rep UserProfilePhotos x -> UserProfilePhotos
forall x. UserProfilePhotos -> Rep UserProfilePhotos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserProfilePhotos x -> UserProfilePhotos
$cfrom :: forall x. UserProfilePhotos -> Rep UserProfilePhotos x
Generic, Int -> UserProfilePhotos -> ShowS
[UserProfilePhotos] -> ShowS
UserProfilePhotos -> String
(Int -> UserProfilePhotos -> ShowS)
-> (UserProfilePhotos -> String)
-> ([UserProfilePhotos] -> ShowS)
-> Show UserProfilePhotos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserProfilePhotos] -> ShowS
$cshowList :: [UserProfilePhotos] -> ShowS
show :: UserProfilePhotos -> String
$cshow :: UserProfilePhotos -> String
showsPrec :: Int -> UserProfilePhotos -> ShowS
$cshowsPrec :: Int -> UserProfilePhotos -> ShowS
Show)
data WebAppData = WebAppData
{ WebAppData -> Text
webAppDataData :: Text
, WebAppData -> Text
webAppDataButtonText :: Text
}
deriving ((forall x. WebAppData -> Rep WebAppData x)
-> (forall x. Rep WebAppData x -> WebAppData) -> Generic WebAppData
forall x. Rep WebAppData x -> WebAppData
forall x. WebAppData -> Rep WebAppData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebAppData x -> WebAppData
$cfrom :: forall x. WebAppData -> Rep WebAppData x
Generic, Int -> WebAppData -> ShowS
[WebAppData] -> ShowS
WebAppData -> String
(Int -> WebAppData -> ShowS)
-> (WebAppData -> String)
-> ([WebAppData] -> ShowS)
-> Show WebAppData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebAppData] -> ShowS
$cshowList :: [WebAppData] -> ShowS
show :: WebAppData -> String
$cshow :: WebAppData -> String
showsPrec :: Int -> WebAppData -> ShowS
$cshowsPrec :: Int -> WebAppData -> ShowS
Show)
data File = File
{ File -> FileId
fileFileId :: FileId
, File -> FileId
fileFileUniqueId :: FileId
, File -> Maybe Int
fileFileSize :: Maybe Int
, File -> Maybe Text
fileFilePath :: Maybe Text
}
deriving ((forall x. File -> Rep File x)
-> (forall x. Rep File x -> File) -> Generic File
forall x. Rep File x -> File
forall x. File -> Rep File x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep File x -> File
$cfrom :: forall x. File -> Rep File x
Generic, Int -> File -> ShowS
[File] -> ShowS
File -> String
(Int -> File -> ShowS)
-> (File -> String) -> ([File] -> ShowS) -> Show File
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [File] -> ShowS
$cshowList :: [File] -> ShowS
show :: File -> String
$cshow :: File -> String
showsPrec :: Int -> File -> ShowS
$cshowsPrec :: Int -> File -> ShowS
Show)
type ContentType = Text
data InputFile
= InputFileId FileId
| FileUrl Text
| InputFile FilePath ContentType
instance ToJSON InputFile where
toJSON :: InputFile -> Value
toJSON (InputFileId FileId
i) = FileId -> Value
forall a. ToJSON a => a -> Value
toJSON FileId
i
toJSON (FileUrl Text
t) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
toJSON (InputFile String
f Text
_) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text
"attach://" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (ShowS
takeFileName String
f))
data ReplyKeyboardMarkup = ReplyKeyboardMarkup
{ ReplyKeyboardMarkup -> [[KeyboardButton]]
replyKeyboardMarkupKeyboard :: [[KeyboardButton]]
, ReplyKeyboardMarkup -> Maybe Bool
replyKeyboardMarkupResizeKeyboard :: Maybe Bool
, ReplyKeyboardMarkup -> Maybe Bool
replyKeyboardMarkupOneTimeKeyboard :: Maybe Bool
, ReplyKeyboardMarkup -> Maybe Text
replyKeyboardMarkupInputFieldSelector :: Maybe Text
, ReplyKeyboardMarkup -> Maybe Bool
replyKeyboardMarkupSelective :: Maybe Bool
}
deriving ((forall x. ReplyKeyboardMarkup -> Rep ReplyKeyboardMarkup x)
-> (forall x. Rep ReplyKeyboardMarkup x -> ReplyKeyboardMarkup)
-> Generic ReplyKeyboardMarkup
forall x. Rep ReplyKeyboardMarkup x -> ReplyKeyboardMarkup
forall x. ReplyKeyboardMarkup -> Rep ReplyKeyboardMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplyKeyboardMarkup x -> ReplyKeyboardMarkup
$cfrom :: forall x. ReplyKeyboardMarkup -> Rep ReplyKeyboardMarkup x
Generic, Int -> ReplyKeyboardMarkup -> ShowS
[ReplyKeyboardMarkup] -> ShowS
ReplyKeyboardMarkup -> String
(Int -> ReplyKeyboardMarkup -> ShowS)
-> (ReplyKeyboardMarkup -> String)
-> ([ReplyKeyboardMarkup] -> ShowS)
-> Show ReplyKeyboardMarkup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplyKeyboardMarkup] -> ShowS
$cshowList :: [ReplyKeyboardMarkup] -> ShowS
show :: ReplyKeyboardMarkup -> String
$cshow :: ReplyKeyboardMarkup -> String
showsPrec :: Int -> ReplyKeyboardMarkup -> ShowS
$cshowsPrec :: Int -> ReplyKeyboardMarkup -> ShowS
Show)
newtype WebAppInfo = WebAppInfo { WebAppInfo -> Text
webAppInfoUrl :: Text }
deriving ((forall x. WebAppInfo -> Rep WebAppInfo x)
-> (forall x. Rep WebAppInfo x -> WebAppInfo) -> Generic WebAppInfo
forall x. Rep WebAppInfo x -> WebAppInfo
forall x. WebAppInfo -> Rep WebAppInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebAppInfo x -> WebAppInfo
$cfrom :: forall x. WebAppInfo -> Rep WebAppInfo x
Generic, Int -> WebAppInfo -> ShowS
[WebAppInfo] -> ShowS
WebAppInfo -> String
(Int -> WebAppInfo -> ShowS)
-> (WebAppInfo -> String)
-> ([WebAppInfo] -> ShowS)
-> Show WebAppInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebAppInfo] -> ShowS
$cshowList :: [WebAppInfo] -> ShowS
show :: WebAppInfo -> String
$cshow :: WebAppInfo -> String
showsPrec :: Int -> WebAppInfo -> ShowS
$cshowsPrec :: Int -> WebAppInfo -> ShowS
Show)
data KeyboardButton = KeyboardButton
{ KeyboardButton -> Text
keyboardButtonText :: Text
, KeyboardButton -> Maybe Bool
keyboardButtonRequestContact :: Maybe Bool
, KeyboardButton -> Maybe Bool
keyboardButtonRequestLocation :: Maybe Bool
, KeyboardButton -> Maybe PollType
keyboardButtonRequestPoll :: Maybe PollType
, KeyboardButton -> Maybe WebAppInfo
keyboardButtonWebApp :: Maybe WebAppInfo
}
deriving ((forall x. KeyboardButton -> Rep KeyboardButton x)
-> (forall x. Rep KeyboardButton x -> KeyboardButton)
-> Generic KeyboardButton
forall x. Rep KeyboardButton x -> KeyboardButton
forall x. KeyboardButton -> Rep KeyboardButton x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeyboardButton x -> KeyboardButton
$cfrom :: forall x. KeyboardButton -> Rep KeyboardButton x
Generic, Int -> KeyboardButton -> ShowS
[KeyboardButton] -> ShowS
KeyboardButton -> String
(Int -> KeyboardButton -> ShowS)
-> (KeyboardButton -> String)
-> ([KeyboardButton] -> ShowS)
-> Show KeyboardButton
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyboardButton] -> ShowS
$cshowList :: [KeyboardButton] -> ShowS
show :: KeyboardButton -> String
$cshow :: KeyboardButton -> String
showsPrec :: Int -> KeyboardButton -> ShowS
$cshowsPrec :: Int -> KeyboardButton -> ShowS
Show)
instance IsString KeyboardButton where
fromString :: String -> KeyboardButton
fromString String
s = Text
-> Maybe Bool
-> Maybe Bool
-> Maybe PollType
-> Maybe WebAppInfo
-> KeyboardButton
KeyboardButton (String -> Text
forall a. IsString a => String -> a
fromString String
s) Maybe Bool
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing Maybe PollType
forall a. Maybe a
Nothing Maybe WebAppInfo
forall a. Maybe a
Nothing
data
= MenuButtonCommands
|
{ MenuButton -> Text
menuButtonWebAppText :: Text
, MenuButton -> WebAppInfo
menuButtonWebAppWebApp :: WebAppInfo
}
|
deriving (forall x. MenuButton -> Rep MenuButton x)
-> (forall x. Rep MenuButton x -> MenuButton) -> Generic MenuButton
forall x. Rep MenuButton x -> MenuButton
forall x. MenuButton -> Rep MenuButton x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MenuButton x -> MenuButton
$cfrom :: forall x. MenuButton -> Rep MenuButton x
Generic
data PollType =
PollTypeQuiz | PollTypeRegular
deriving ((forall x. PollType -> Rep PollType x)
-> (forall x. Rep PollType x -> PollType) -> Generic PollType
forall x. Rep PollType x -> PollType
forall x. PollType -> Rep PollType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PollType x -> PollType
$cfrom :: forall x. PollType -> Rep PollType x
Generic, Int -> PollType -> ShowS
[PollType] -> ShowS
PollType -> String
(Int -> PollType -> ShowS)
-> (PollType -> String) -> ([PollType] -> ShowS) -> Show PollType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollType] -> ShowS
$cshowList :: [PollType] -> ShowS
show :: PollType -> String
$cshow :: PollType -> String
showsPrec :: Int -> PollType -> ShowS
$cshowsPrec :: Int -> PollType -> ShowS
Show)
getPollType :: PollType -> Text
getPollType :: PollType -> Text
getPollType PollType
PollTypeQuiz = Text
"quiz"
getPollType PollType
PollTypeRegular = Text
"regular"
instance ToJSON PollType where
toJSON :: PollType -> Value
toJSON = Text -> Value
String (Text -> Value) -> (PollType -> Text) -> PollType -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PollType -> Text
getPollType
instance FromJSON PollType where parseJSON :: Value -> Parser PollType
parseJSON = Value -> Parser PollType
forall a (d :: Meta) (f :: * -> *).
(Generic a, GFromJSON Zero (Rep a), Rep a ~ D1 d f, Datatype d) =>
Value -> Parser a
gparseJSON
data ReplyKeyboardRemove = ReplyKeyboardRemove
{ ReplyKeyboardRemove -> Bool
replyKeyboardRemoveRemoveKeyboard :: Bool
, ReplyKeyboardRemove -> Maybe Bool
replyKeyboardRemoveSelective :: Maybe Bool
}
deriving ((forall x. ReplyKeyboardRemove -> Rep ReplyKeyboardRemove x)
-> (forall x. Rep ReplyKeyboardRemove x -> ReplyKeyboardRemove)
-> Generic ReplyKeyboardRemove
forall x. Rep ReplyKeyboardRemove x -> ReplyKeyboardRemove
forall x. ReplyKeyboardRemove -> Rep ReplyKeyboardRemove x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplyKeyboardRemove x -> ReplyKeyboardRemove
$cfrom :: forall x. ReplyKeyboardRemove -> Rep ReplyKeyboardRemove x
Generic, Int -> ReplyKeyboardRemove -> ShowS
[ReplyKeyboardRemove] -> ShowS
ReplyKeyboardRemove -> String
(Int -> ReplyKeyboardRemove -> ShowS)
-> (ReplyKeyboardRemove -> String)
-> ([ReplyKeyboardRemove] -> ShowS)
-> Show ReplyKeyboardRemove
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplyKeyboardRemove] -> ShowS
$cshowList :: [ReplyKeyboardRemove] -> ShowS
show :: ReplyKeyboardRemove -> String
$cshow :: ReplyKeyboardRemove -> String
showsPrec :: Int -> ReplyKeyboardRemove -> ShowS
$cshowsPrec :: Int -> ReplyKeyboardRemove -> ShowS
Show)
data InlineKeyboardMarkup = InlineKeyboardMarkup
{ InlineKeyboardMarkup -> [[InlineKeyboardButton]]
inlineKeyboardMarkupInlineKeyboard :: [[InlineKeyboardButton]]
}
deriving ((forall x. InlineKeyboardMarkup -> Rep InlineKeyboardMarkup x)
-> (forall x. Rep InlineKeyboardMarkup x -> InlineKeyboardMarkup)
-> Generic InlineKeyboardMarkup
forall x. Rep InlineKeyboardMarkup x -> InlineKeyboardMarkup
forall x. InlineKeyboardMarkup -> Rep InlineKeyboardMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineKeyboardMarkup x -> InlineKeyboardMarkup
$cfrom :: forall x. InlineKeyboardMarkup -> Rep InlineKeyboardMarkup x
Generic, Int -> InlineKeyboardMarkup -> ShowS
[InlineKeyboardMarkup] -> ShowS
InlineKeyboardMarkup -> String
(Int -> InlineKeyboardMarkup -> ShowS)
-> (InlineKeyboardMarkup -> String)
-> ([InlineKeyboardMarkup] -> ShowS)
-> Show InlineKeyboardMarkup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineKeyboardMarkup] -> ShowS
$cshowList :: [InlineKeyboardMarkup] -> ShowS
show :: InlineKeyboardMarkup -> String
$cshow :: InlineKeyboardMarkup -> String
showsPrec :: Int -> InlineKeyboardMarkup -> ShowS
$cshowsPrec :: Int -> InlineKeyboardMarkup -> ShowS
Show)
data InlineKeyboardButton = InlineKeyboardButton
{ InlineKeyboardButton -> Text
inlineKeyboardButtonText :: Text
, InlineKeyboardButton -> Maybe Text
inlineKeyboardButtonUrl :: Maybe Text
, InlineKeyboardButton -> Maybe Text
inlineKeyboardButtonCallbackData :: Maybe Text
, InlineKeyboardButton -> Maybe WebAppInfo
inlineKeyboardButtonWebApp :: Maybe WebAppInfo
, InlineKeyboardButton -> Maybe Text
inlineKeyboardButtonSwitchInlineQuery :: Maybe Text
, InlineKeyboardButton -> Maybe Text
inlineKeyboardButtonSwitchInlineQueryCurrentChat :: Maybe Text
, InlineKeyboardButton -> Maybe CallbackGame
inlineKeyboardButtonCallbackGame :: Maybe CallbackGame
, InlineKeyboardButton -> Maybe Bool
inlineKeyboardButtonPay :: Maybe Bool
}
deriving ((forall x. InlineKeyboardButton -> Rep InlineKeyboardButton x)
-> (forall x. Rep InlineKeyboardButton x -> InlineKeyboardButton)
-> Generic InlineKeyboardButton
forall x. Rep InlineKeyboardButton x -> InlineKeyboardButton
forall x. InlineKeyboardButton -> Rep InlineKeyboardButton x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineKeyboardButton x -> InlineKeyboardButton
$cfrom :: forall x. InlineKeyboardButton -> Rep InlineKeyboardButton x
Generic, Int -> InlineKeyboardButton -> ShowS
[InlineKeyboardButton] -> ShowS
InlineKeyboardButton -> String
(Int -> InlineKeyboardButton -> ShowS)
-> (InlineKeyboardButton -> String)
-> ([InlineKeyboardButton] -> ShowS)
-> Show InlineKeyboardButton
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineKeyboardButton] -> ShowS
$cshowList :: [InlineKeyboardButton] -> ShowS
show :: InlineKeyboardButton -> String
$cshow :: InlineKeyboardButton -> String
showsPrec :: Int -> InlineKeyboardButton -> ShowS
$cshowsPrec :: Int -> InlineKeyboardButton -> ShowS
Show)
labeledInlineKeyboardButton :: Text -> InlineKeyboardButton
labeledInlineKeyboardButton :: Text -> InlineKeyboardButton
labeledInlineKeyboardButton Text
label = Text
-> Maybe Text
-> Maybe Text
-> Maybe WebAppInfo
-> Maybe Text
-> Maybe Text
-> Maybe CallbackGame
-> Maybe Bool
-> InlineKeyboardButton
InlineKeyboardButton Text
label Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe WebAppInfo
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe Text
forall a. Maybe a
Nothing Maybe CallbackGame
forall a. Maybe a
Nothing Maybe Bool
forall a. Maybe a
Nothing
data LoginUrl = LoginUrl
{ LoginUrl -> Text
loginUrlUrl :: Text
, LoginUrl -> Maybe Text
loginUrlForwardText :: Maybe Text
, LoginUrl -> Maybe Text
loginUrlBotUsername :: Maybe Text
, LoginUrl -> Maybe Bool
loginUrlRequestWriteAccess :: Maybe Bool
}
deriving ((forall x. LoginUrl -> Rep LoginUrl x)
-> (forall x. Rep LoginUrl x -> LoginUrl) -> Generic LoginUrl
forall x. Rep LoginUrl x -> LoginUrl
forall x. LoginUrl -> Rep LoginUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LoginUrl x -> LoginUrl
$cfrom :: forall x. LoginUrl -> Rep LoginUrl x
Generic, Int -> LoginUrl -> ShowS
[LoginUrl] -> ShowS
LoginUrl -> String
(Int -> LoginUrl -> ShowS)
-> (LoginUrl -> String) -> ([LoginUrl] -> ShowS) -> Show LoginUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoginUrl] -> ShowS
$cshowList :: [LoginUrl] -> ShowS
show :: LoginUrl -> String
$cshow :: LoginUrl -> String
showsPrec :: Int -> LoginUrl -> ShowS
$cshowsPrec :: Int -> LoginUrl -> ShowS
Show)
data CallbackQuery = CallbackQuery
{ CallbackQuery -> CallbackQueryId
callbackQueryId :: CallbackQueryId
, CallbackQuery -> User
callbackQueryFrom :: User
, CallbackQuery -> Maybe Message
callbackQueryMessage :: Maybe Message
, CallbackQuery -> Maybe MessageId
callbackQueryInlineMessageId :: Maybe MessageId
, CallbackQuery -> Text
callbackQueryChatInstance :: Text
, CallbackQuery -> Maybe Text
callbackQueryData :: Maybe Text
, CallbackQuery -> Maybe Text
callbackQueryGameShortName :: Maybe Text
}
deriving ((forall x. CallbackQuery -> Rep CallbackQuery x)
-> (forall x. Rep CallbackQuery x -> CallbackQuery)
-> Generic CallbackQuery
forall x. Rep CallbackQuery x -> CallbackQuery
forall x. CallbackQuery -> Rep CallbackQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallbackQuery x -> CallbackQuery
$cfrom :: forall x. CallbackQuery -> Rep CallbackQuery x
Generic, Int -> CallbackQuery -> ShowS
[CallbackQuery] -> ShowS
CallbackQuery -> String
(Int -> CallbackQuery -> ShowS)
-> (CallbackQuery -> String)
-> ([CallbackQuery] -> ShowS)
-> Show CallbackQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallbackQuery] -> ShowS
$cshowList :: [CallbackQuery] -> ShowS
show :: CallbackQuery -> String
$cshow :: CallbackQuery -> String
showsPrec :: Int -> CallbackQuery -> ShowS
$cshowsPrec :: Int -> CallbackQuery -> ShowS
Show)
newtype CallbackQueryId = CallbackQueryId Text
deriving (CallbackQueryId -> CallbackQueryId -> Bool
(CallbackQueryId -> CallbackQueryId -> Bool)
-> (CallbackQueryId -> CallbackQueryId -> Bool)
-> Eq CallbackQueryId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallbackQueryId -> CallbackQueryId -> Bool
$c/= :: CallbackQueryId -> CallbackQueryId -> Bool
== :: CallbackQueryId -> CallbackQueryId -> Bool
$c== :: CallbackQueryId -> CallbackQueryId -> Bool
Eq, Int -> CallbackQueryId -> ShowS
[CallbackQueryId] -> ShowS
CallbackQueryId -> String
(Int -> CallbackQueryId -> ShowS)
-> (CallbackQueryId -> String)
-> ([CallbackQueryId] -> ShowS)
-> Show CallbackQueryId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallbackQueryId] -> ShowS
$cshowList :: [CallbackQueryId] -> ShowS
show :: CallbackQueryId -> String
$cshow :: CallbackQueryId -> String
showsPrec :: Int -> CallbackQueryId -> ShowS
$cshowsPrec :: Int -> CallbackQueryId -> ShowS
Show, (forall x. CallbackQueryId -> Rep CallbackQueryId x)
-> (forall x. Rep CallbackQueryId x -> CallbackQueryId)
-> Generic CallbackQueryId
forall x. Rep CallbackQueryId x -> CallbackQueryId
forall x. CallbackQueryId -> Rep CallbackQueryId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallbackQueryId x -> CallbackQueryId
$cfrom :: forall x. CallbackQueryId -> Rep CallbackQueryId x
Generic, [CallbackQueryId] -> Encoding
[CallbackQueryId] -> Value
CallbackQueryId -> Encoding
CallbackQueryId -> Value
(CallbackQueryId -> Value)
-> (CallbackQueryId -> Encoding)
-> ([CallbackQueryId] -> Value)
-> ([CallbackQueryId] -> Encoding)
-> ToJSON CallbackQueryId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [CallbackQueryId] -> Encoding
$ctoEncodingList :: [CallbackQueryId] -> Encoding
toJSONList :: [CallbackQueryId] -> Value
$ctoJSONList :: [CallbackQueryId] -> Value
toEncoding :: CallbackQueryId -> Encoding
$ctoEncoding :: CallbackQueryId -> Encoding
toJSON :: CallbackQueryId -> Value
$ctoJSON :: CallbackQueryId -> Value
ToJSON, Value -> Parser [CallbackQueryId]
Value -> Parser CallbackQueryId
(Value -> Parser CallbackQueryId)
-> (Value -> Parser [CallbackQueryId]) -> FromJSON CallbackQueryId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [CallbackQueryId]
$cparseJSONList :: Value -> Parser [CallbackQueryId]
parseJSON :: Value -> Parser CallbackQueryId
$cparseJSON :: Value -> Parser CallbackQueryId
FromJSON)
data ForceReply = ForceReply
{ ForceReply -> Bool
forceReplyForceReply :: Bool
, ForceReply -> Maybe Text
forceReplyInputFieldPlaceholder :: Maybe Text
, ForceReply -> Maybe Bool
forceReplySelective :: Maybe Bool
}
deriving ((forall x. ForceReply -> Rep ForceReply x)
-> (forall x. Rep ForceReply x -> ForceReply) -> Generic ForceReply
forall x. Rep ForceReply x -> ForceReply
forall x. ForceReply -> Rep ForceReply x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForceReply x -> ForceReply
$cfrom :: forall x. ForceReply -> Rep ForceReply x
Generic, Int -> ForceReply -> ShowS
[ForceReply] -> ShowS
ForceReply -> String
(Int -> ForceReply -> ShowS)
-> (ForceReply -> String)
-> ([ForceReply] -> ShowS)
-> Show ForceReply
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForceReply] -> ShowS
$cshowList :: [ForceReply] -> ShowS
show :: ForceReply -> String
$cshow :: ForceReply -> String
showsPrec :: Int -> ForceReply -> ShowS
$cshowsPrec :: Int -> ForceReply -> ShowS
Show)
data ChatPhoto = ChatPhoto
{ ChatPhoto -> FileId
chatPhotoSmallFileId :: FileId
, ChatPhoto -> FileId
chatPhotoSmallFileUniqueId :: FileId
, ChatPhoto -> FileId
chatPhotoBigFileId :: FileId
, ChatPhoto -> FileId
chatPhotoBigFileUniqueId :: FileId
}
deriving ((forall x. ChatPhoto -> Rep ChatPhoto x)
-> (forall x. Rep ChatPhoto x -> ChatPhoto) -> Generic ChatPhoto
forall x. Rep ChatPhoto x -> ChatPhoto
forall x. ChatPhoto -> Rep ChatPhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatPhoto x -> ChatPhoto
$cfrom :: forall x. ChatPhoto -> Rep ChatPhoto x
Generic, Int -> ChatPhoto -> ShowS
[ChatPhoto] -> ShowS
ChatPhoto -> String
(Int -> ChatPhoto -> ShowS)
-> (ChatPhoto -> String)
-> ([ChatPhoto] -> ShowS)
-> Show ChatPhoto
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatPhoto] -> ShowS
$cshowList :: [ChatPhoto] -> ShowS
show :: ChatPhoto -> String
$cshow :: ChatPhoto -> String
showsPrec :: Int -> ChatPhoto -> ShowS
$cshowsPrec :: Int -> ChatPhoto -> ShowS
Show)
data ChatInviteLink = ChatInviteLink
{ ChatInviteLink -> Text
chatInviteLinkInviteLink :: Text
, ChatInviteLink -> User
chatInviteLinkCreator :: User
, ChatInviteLink -> Bool
chatInviteLinkCreatesJoinRequest :: Bool
, ChatInviteLink -> Bool
chatInviteLinkIsPrimary :: Bool
, ChatInviteLink -> Bool
chatInviteLinkIsRevoked :: Bool
, ChatInviteLink -> Maybe Text
chatInviteLinkName :: Maybe Text
, ChatInviteLink -> Maybe POSIXTime
chatInviteLinkExpireDate :: Maybe POSIXTime
, ChatInviteLink -> Maybe Int
chatInviteLinkMemberLimit :: Maybe Int
, ChatInviteLink -> Maybe Int
chatInviteLinkPendingJoinRequestCount :: Maybe Int
}
deriving ((forall x. ChatInviteLink -> Rep ChatInviteLink x)
-> (forall x. Rep ChatInviteLink x -> ChatInviteLink)
-> Generic ChatInviteLink
forall x. Rep ChatInviteLink x -> ChatInviteLink
forall x. ChatInviteLink -> Rep ChatInviteLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatInviteLink x -> ChatInviteLink
$cfrom :: forall x. ChatInviteLink -> Rep ChatInviteLink x
Generic, Int -> ChatInviteLink -> ShowS
[ChatInviteLink] -> ShowS
ChatInviteLink -> String
(Int -> ChatInviteLink -> ShowS)
-> (ChatInviteLink -> String)
-> ([ChatInviteLink] -> ShowS)
-> Show ChatInviteLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatInviteLink] -> ShowS
$cshowList :: [ChatInviteLink] -> ShowS
show :: ChatInviteLink -> String
$cshow :: ChatInviteLink -> String
showsPrec :: Int -> ChatInviteLink -> ShowS
$cshowsPrec :: Int -> ChatInviteLink -> ShowS
Show)
data ChatAdministratorRights = ChatAdministratorRights
{ ChatAdministratorRights -> Bool
chatAdministratorRightsIsAnonymous :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanManageChat :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanDeleteMessages :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanManageVideoChats :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanRestrictMembers :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanPromoteMembers :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanChangeInfo :: Bool
, ChatAdministratorRights -> Bool
chatAdministratorRightsCanInviteUsers :: Bool
, ChatAdministratorRights -> Maybe Bool
chatAdministratorRightsCanPostMessages :: Maybe Bool
, ChatAdministratorRights -> Maybe Bool
chatAdministratorRightsCanEditMessages :: Maybe Bool
, ChatAdministratorRights -> Maybe Bool
chatAdministratorRightsCanPinMessages :: Maybe Bool
}
deriving ((forall x.
ChatAdministratorRights -> Rep ChatAdministratorRights x)
-> (forall x.
Rep ChatAdministratorRights x -> ChatAdministratorRights)
-> Generic ChatAdministratorRights
forall x. Rep ChatAdministratorRights x -> ChatAdministratorRights
forall x. ChatAdministratorRights -> Rep ChatAdministratorRights x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatAdministratorRights x -> ChatAdministratorRights
$cfrom :: forall x. ChatAdministratorRights -> Rep ChatAdministratorRights x
Generic, Int -> ChatAdministratorRights -> ShowS
[ChatAdministratorRights] -> ShowS
ChatAdministratorRights -> String
(Int -> ChatAdministratorRights -> ShowS)
-> (ChatAdministratorRights -> String)
-> ([ChatAdministratorRights] -> ShowS)
-> Show ChatAdministratorRights
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatAdministratorRights] -> ShowS
$cshowList :: [ChatAdministratorRights] -> ShowS
show :: ChatAdministratorRights -> String
$cshow :: ChatAdministratorRights -> String
showsPrec :: Int -> ChatAdministratorRights -> ShowS
$cshowsPrec :: Int -> ChatAdministratorRights -> ShowS
Show)
data ChatMember = ChatMember
{ ChatMember -> User
chatMemberUser :: User
, ChatMember -> Text
chatMemberStatus :: Text
, ChatMember -> Maybe POSIXTime
chatMemberUntilDate :: Maybe POSIXTime
, ChatMember -> Maybe Bool
chatMemberIsAnonymous :: Maybe Bool
, ChatMember -> Maybe Text
chatMemberCustomTitle :: Maybe Text
, ChatMember -> Maybe Bool
chatMemberCanBeEdited :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanManageChat :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanDeleteMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanManageVideoChats :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanRestrictMembers :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanPromoteMembers :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanChangeInfo :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanPostMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanEditMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanInviteUsers :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanPinMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberIsMember :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanSendMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanSendMediaMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanSendPolls :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanSendOtherMessages :: Maybe Bool
, ChatMember -> Maybe Bool
chatMemberCanAddWebPagePreviews :: Maybe Bool
}
deriving ((forall x. ChatMember -> Rep ChatMember x)
-> (forall x. Rep ChatMember x -> ChatMember) -> Generic ChatMember
forall x. Rep ChatMember x -> ChatMember
forall x. ChatMember -> Rep ChatMember x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatMember x -> ChatMember
$cfrom :: forall x. ChatMember -> Rep ChatMember x
Generic, Int -> ChatMember -> ShowS
[ChatMember] -> ShowS
ChatMember -> String
(Int -> ChatMember -> ShowS)
-> (ChatMember -> String)
-> ([ChatMember] -> ShowS)
-> Show ChatMember
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMember] -> ShowS
$cshowList :: [ChatMember] -> ShowS
show :: ChatMember -> String
$cshow :: ChatMember -> String
showsPrec :: Int -> ChatMember -> ShowS
$cshowsPrec :: Int -> ChatMember -> ShowS
Show)
data ChatMemberUpdated = ChatMemberUpdated
{ ChatMemberUpdated -> Chat
chatMemberUpdatedChat :: Chat
, ChatMemberUpdated -> User
chatMemberUpdatedFrom :: User
, ChatMemberUpdated -> POSIXTime
chatMemberUpdatedDate :: POSIXTime
, ChatMemberUpdated -> ChatMember
chatMemberUpdatedOldChatMember :: ChatMember
, ChatMemberUpdated -> ChatMember
chatMemberUpdatedNewChatMember :: ChatMember
, ChatMemberUpdated -> Maybe ChatInviteLink
chatMemberUpdatedInviteLink :: Maybe ChatInviteLink
}
deriving ((forall x. ChatMemberUpdated -> Rep ChatMemberUpdated x)
-> (forall x. Rep ChatMemberUpdated x -> ChatMemberUpdated)
-> Generic ChatMemberUpdated
forall x. Rep ChatMemberUpdated x -> ChatMemberUpdated
forall x. ChatMemberUpdated -> Rep ChatMemberUpdated x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatMemberUpdated x -> ChatMemberUpdated
$cfrom :: forall x. ChatMemberUpdated -> Rep ChatMemberUpdated x
Generic, Int -> ChatMemberUpdated -> ShowS
[ChatMemberUpdated] -> ShowS
ChatMemberUpdated -> String
(Int -> ChatMemberUpdated -> ShowS)
-> (ChatMemberUpdated -> String)
-> ([ChatMemberUpdated] -> ShowS)
-> Show ChatMemberUpdated
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMemberUpdated] -> ShowS
$cshowList :: [ChatMemberUpdated] -> ShowS
show :: ChatMemberUpdated -> String
$cshow :: ChatMemberUpdated -> String
showsPrec :: Int -> ChatMemberUpdated -> ShowS
$cshowsPrec :: Int -> ChatMemberUpdated -> ShowS
Show)
data ChatJoinRequest = ChatJoinRequest
{ ChatJoinRequest -> Chat
chatJoinRequestChat :: Chat
, ChatJoinRequest -> User
chatJoinRequestFrom :: User
, ChatJoinRequest -> POSIXTime
chatJoinRequestDate :: POSIXTime
, ChatJoinRequest -> Maybe Text
chatJoinRequestBio :: Maybe Text
, ChatJoinRequest -> Maybe ChatInviteLink
chatJoinRequestInviteLink :: Maybe ChatInviteLink
}
deriving ((forall x. ChatJoinRequest -> Rep ChatJoinRequest x)
-> (forall x. Rep ChatJoinRequest x -> ChatJoinRequest)
-> Generic ChatJoinRequest
forall x. Rep ChatJoinRequest x -> ChatJoinRequest
forall x. ChatJoinRequest -> Rep ChatJoinRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatJoinRequest x -> ChatJoinRequest
$cfrom :: forall x. ChatJoinRequest -> Rep ChatJoinRequest x
Generic, Int -> ChatJoinRequest -> ShowS
[ChatJoinRequest] -> ShowS
ChatJoinRequest -> String
(Int -> ChatJoinRequest -> ShowS)
-> (ChatJoinRequest -> String)
-> ([ChatJoinRequest] -> ShowS)
-> Show ChatJoinRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatJoinRequest] -> ShowS
$cshowList :: [ChatJoinRequest] -> ShowS
show :: ChatJoinRequest -> String
$cshow :: ChatJoinRequest -> String
showsPrec :: Int -> ChatJoinRequest -> ShowS
$cshowsPrec :: Int -> ChatJoinRequest -> ShowS
Show)
data ChatPermissions = ChatPermissions
{ ChatPermissions -> Maybe Bool
chatPermissionsCanSendMessages :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanSendMediaMessages :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanSendPolls :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanSendOtherMessages :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanAddWebPagePreviews :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanChangeInfo :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanInviteUsers :: Maybe Bool
, ChatPermissions -> Maybe Bool
chatPermissionsCanPinMessages :: Maybe Bool
}
deriving ((forall x. ChatPermissions -> Rep ChatPermissions x)
-> (forall x. Rep ChatPermissions x -> ChatPermissions)
-> Generic ChatPermissions
forall x. Rep ChatPermissions x -> ChatPermissions
forall x. ChatPermissions -> Rep ChatPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatPermissions x -> ChatPermissions
$cfrom :: forall x. ChatPermissions -> Rep ChatPermissions x
Generic, Int -> ChatPermissions -> ShowS
[ChatPermissions] -> ShowS
ChatPermissions -> String
(Int -> ChatPermissions -> ShowS)
-> (ChatPermissions -> String)
-> ([ChatPermissions] -> ShowS)
-> Show ChatPermissions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatPermissions] -> ShowS
$cshowList :: [ChatPermissions] -> ShowS
show :: ChatPermissions -> String
$cshow :: ChatPermissions -> String
showsPrec :: Int -> ChatPermissions -> ShowS
$cshowsPrec :: Int -> ChatPermissions -> ShowS
Show)
data ChatLocation = ChatLocation
{ ChatLocation -> Location
chatLocationLocation :: Location
, ChatLocation -> Text
chatLocationAddress :: Text
}
deriving ((forall x. ChatLocation -> Rep ChatLocation x)
-> (forall x. Rep ChatLocation x -> ChatLocation)
-> Generic ChatLocation
forall x. Rep ChatLocation x -> ChatLocation
forall x. ChatLocation -> Rep ChatLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatLocation x -> ChatLocation
$cfrom :: forall x. ChatLocation -> Rep ChatLocation x
Generic, Int -> ChatLocation -> ShowS
[ChatLocation] -> ShowS
ChatLocation -> String
(Int -> ChatLocation -> ShowS)
-> (ChatLocation -> String)
-> ([ChatLocation] -> ShowS)
-> Show ChatLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatLocation] -> ShowS
$cshowList :: [ChatLocation] -> ShowS
show :: ChatLocation -> String
$cshow :: ChatLocation -> String
showsPrec :: Int -> ChatLocation -> ShowS
$cshowsPrec :: Int -> ChatLocation -> ShowS
Show)
data ResponseParameters = ResponseParameters
{ ResponseParameters -> Maybe ChatId
responseParametersMigrateToChatId :: Maybe ChatId
, ResponseParameters -> Maybe Seconds
responseParametersRetryAfter :: Maybe Seconds
}
deriving (Int -> ResponseParameters -> ShowS
[ResponseParameters] -> ShowS
ResponseParameters -> String
(Int -> ResponseParameters -> ShowS)
-> (ResponseParameters -> String)
-> ([ResponseParameters] -> ShowS)
-> Show ResponseParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResponseParameters] -> ShowS
$cshowList :: [ResponseParameters] -> ShowS
show :: ResponseParameters -> String
$cshow :: ResponseParameters -> String
showsPrec :: Int -> ResponseParameters -> ShowS
$cshowsPrec :: Int -> ResponseParameters -> ShowS
Show, (forall x. ResponseParameters -> Rep ResponseParameters x)
-> (forall x. Rep ResponseParameters x -> ResponseParameters)
-> Generic ResponseParameters
forall x. Rep ResponseParameters x -> ResponseParameters
forall x. ResponseParameters -> Rep ResponseParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResponseParameters x -> ResponseParameters
$cfrom :: forall x. ResponseParameters -> Rep ResponseParameters x
Generic)
data Sticker = Sticker
{ Sticker -> FileId
stickerFileId :: FileId
, Sticker -> FileId
stickerFileUniqueId :: FileId
, Sticker -> Int
stickerWidth :: Int
, Sticker -> Int
stickerHeight :: Int
, Sticker -> Bool
stickerIsAnimated :: Bool
, Sticker -> Bool
stickerIsVideo :: Bool
, Sticker -> Maybe PhotoSize
stickerThumb :: Maybe PhotoSize
, Sticker -> Maybe Text
stickerEmoji :: Maybe Text
, Sticker -> Maybe Text
stickerSetName :: Maybe Text
, Sticker -> Maybe MaskPosition
stickerMaskPosition :: Maybe MaskPosition
, Sticker -> Maybe Integer
stickerFileSize :: Maybe Integer
}
deriving ((forall x. Sticker -> Rep Sticker x)
-> (forall x. Rep Sticker x -> Sticker) -> Generic Sticker
forall x. Rep Sticker x -> Sticker
forall x. Sticker -> Rep Sticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Sticker x -> Sticker
$cfrom :: forall x. Sticker -> Rep Sticker x
Generic, Int -> Sticker -> ShowS
[Sticker] -> ShowS
Sticker -> String
(Int -> Sticker -> ShowS)
-> (Sticker -> String) -> ([Sticker] -> ShowS) -> Show Sticker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Sticker] -> ShowS
$cshowList :: [Sticker] -> ShowS
show :: Sticker -> String
$cshow :: Sticker -> String
showsPrec :: Int -> Sticker -> ShowS
$cshowsPrec :: Int -> Sticker -> ShowS
Show)
data StickerSet = StickerSet
{ StickerSet -> Text
stickerSetName :: Text
, StickerSet -> Text
stickerSetTitle :: Text
, StickerSet -> Bool
stickerSetIsAnimated :: Bool
, StickerSet -> Bool
stickerSetIsVideo :: Bool
, StickerSet -> Bool
stickerSetContainsMasks :: Bool
, StickerSet -> [Sticker]
stickerSetStickers :: [Sticker]
, StickerSet -> Maybe PhotoSize
stickerSetThumb :: Maybe PhotoSize
}
deriving ((forall x. StickerSet -> Rep StickerSet x)
-> (forall x. Rep StickerSet x -> StickerSet) -> Generic StickerSet
forall x. Rep StickerSet x -> StickerSet
forall x. StickerSet -> Rep StickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StickerSet x -> StickerSet
$cfrom :: forall x. StickerSet -> Rep StickerSet x
Generic, Int -> StickerSet -> ShowS
[StickerSet] -> ShowS
StickerSet -> String
(Int -> StickerSet -> ShowS)
-> (StickerSet -> String)
-> ([StickerSet] -> ShowS)
-> Show StickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StickerSet] -> ShowS
$cshowList :: [StickerSet] -> ShowS
show :: StickerSet -> String
$cshow :: StickerSet -> String
showsPrec :: Int -> StickerSet -> ShowS
$cshowsPrec :: Int -> StickerSet -> ShowS
Show)
data MaskPosition = MaskPosition
{ MaskPosition -> Text
maskPositionPoint :: Text
, MaskPosition -> Float
maskPositionXShift :: Float
, MaskPosition -> Float
maskPositionYShift :: Float
, MaskPosition -> Float
maskPositionScale :: Float
}
deriving ((forall x. MaskPosition -> Rep MaskPosition x)
-> (forall x. Rep MaskPosition x -> MaskPosition)
-> Generic MaskPosition
forall x. Rep MaskPosition x -> MaskPosition
forall x. MaskPosition -> Rep MaskPosition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MaskPosition x -> MaskPosition
$cfrom :: forall x. MaskPosition -> Rep MaskPosition x
Generic, Int -> MaskPosition -> ShowS
[MaskPosition] -> ShowS
MaskPosition -> String
(Int -> MaskPosition -> ShowS)
-> (MaskPosition -> String)
-> ([MaskPosition] -> ShowS)
-> Show MaskPosition
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaskPosition] -> ShowS
$cshowList :: [MaskPosition] -> ShowS
show :: MaskPosition -> String
$cshow :: MaskPosition -> String
showsPrec :: Int -> MaskPosition -> ShowS
$cshowsPrec :: Int -> MaskPosition -> ShowS
Show)
data LabeledPrice = LabelPrice
{ LabeledPrice -> Text
labeledPriceLabel :: Text
, LabeledPrice -> Int
labeledPriceAmount :: Int
}
deriving ((forall x. LabeledPrice -> Rep LabeledPrice x)
-> (forall x. Rep LabeledPrice x -> LabeledPrice)
-> Generic LabeledPrice
forall x. Rep LabeledPrice x -> LabeledPrice
forall x. LabeledPrice -> Rep LabeledPrice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LabeledPrice x -> LabeledPrice
$cfrom :: forall x. LabeledPrice -> Rep LabeledPrice x
Generic, Int -> LabeledPrice -> ShowS
[LabeledPrice] -> ShowS
LabeledPrice -> String
(Int -> LabeledPrice -> ShowS)
-> (LabeledPrice -> String)
-> ([LabeledPrice] -> ShowS)
-> Show LabeledPrice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LabeledPrice] -> ShowS
$cshowList :: [LabeledPrice] -> ShowS
show :: LabeledPrice -> String
$cshow :: LabeledPrice -> String
showsPrec :: Int -> LabeledPrice -> ShowS
$cshowsPrec :: Int -> LabeledPrice -> ShowS
Show)
data Invoice = Invoice
{ Invoice -> Text
invoiceTitle :: Text
, Invoice -> Text
invoiceDescription :: Text
, Invoice -> Text
invoiceStartParameter :: Text
, Invoice -> Text
invoiceCurrency :: Text
, Invoice -> Int
invoiceTotalAmount :: Int
}
deriving ((forall x. Invoice -> Rep Invoice x)
-> (forall x. Rep Invoice x -> Invoice) -> Generic Invoice
forall x. Rep Invoice x -> Invoice
forall x. Invoice -> Rep Invoice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Invoice x -> Invoice
$cfrom :: forall x. Invoice -> Rep Invoice x
Generic, Int -> Invoice -> ShowS
[Invoice] -> ShowS
Invoice -> String
(Int -> Invoice -> ShowS)
-> (Invoice -> String) -> ([Invoice] -> ShowS) -> Show Invoice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Invoice] -> ShowS
$cshowList :: [Invoice] -> ShowS
show :: Invoice -> String
$cshow :: Invoice -> String
showsPrec :: Int -> Invoice -> ShowS
$cshowsPrec :: Int -> Invoice -> ShowS
Show)
data ShippingAddress = ShippingAddress
{ ShippingAddress -> Text
shippingAddressCountryCode :: Text
, ShippingAddress -> Text
shippingAddressState :: Text
, ShippingAddress -> Text
shippingAddressCity :: Text
, ShippingAddress -> Text
shippingAddressStreetLine1 :: Text
, ShippingAddress -> Text
shippingAddressStreetLine2 :: Text
, ShippingAddress -> Text
shippingAddressPostCode :: Text
}
deriving ((forall x. ShippingAddress -> Rep ShippingAddress x)
-> (forall x. Rep ShippingAddress x -> ShippingAddress)
-> Generic ShippingAddress
forall x. Rep ShippingAddress x -> ShippingAddress
forall x. ShippingAddress -> Rep ShippingAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShippingAddress x -> ShippingAddress
$cfrom :: forall x. ShippingAddress -> Rep ShippingAddress x
Generic, Int -> ShippingAddress -> ShowS
[ShippingAddress] -> ShowS
ShippingAddress -> String
(Int -> ShippingAddress -> ShowS)
-> (ShippingAddress -> String)
-> ([ShippingAddress] -> ShowS)
-> Show ShippingAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShippingAddress] -> ShowS
$cshowList :: [ShippingAddress] -> ShowS
show :: ShippingAddress -> String
$cshow :: ShippingAddress -> String
showsPrec :: Int -> ShippingAddress -> ShowS
$cshowsPrec :: Int -> ShippingAddress -> ShowS
Show)
data OrderInfo = OrderInfo
{ OrderInfo -> Maybe Text
orderInfoName :: Maybe Text
, OrderInfo -> Maybe Text
orderInfoPhoneNumber :: Maybe Text
, OrderInfo -> Maybe Text
orderInfoEmail :: Maybe Text
, OrderInfo -> Maybe ShippingAddress
orderInfoShippingAddress :: Maybe ShippingAddress
}
deriving ((forall x. OrderInfo -> Rep OrderInfo x)
-> (forall x. Rep OrderInfo x -> OrderInfo) -> Generic OrderInfo
forall x. Rep OrderInfo x -> OrderInfo
forall x. OrderInfo -> Rep OrderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OrderInfo x -> OrderInfo
$cfrom :: forall x. OrderInfo -> Rep OrderInfo x
Generic, Int -> OrderInfo -> ShowS
[OrderInfo] -> ShowS
OrderInfo -> String
(Int -> OrderInfo -> ShowS)
-> (OrderInfo -> String)
-> ([OrderInfo] -> ShowS)
-> Show OrderInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OrderInfo] -> ShowS
$cshowList :: [OrderInfo] -> ShowS
show :: OrderInfo -> String
$cshow :: OrderInfo -> String
showsPrec :: Int -> OrderInfo -> ShowS
$cshowsPrec :: Int -> OrderInfo -> ShowS
Show)
data ShippingOption = ShippingOption
{ ShippingOption -> ShippingOptionId
shippingOptionId :: ShippingOptionId
, ShippingOption -> Text
shippingOptionTitle :: Text
, ShippingOption -> [LabeledPrice]
shippingOptionPrice :: [LabeledPrice]
}
deriving ((forall x. ShippingOption -> Rep ShippingOption x)
-> (forall x. Rep ShippingOption x -> ShippingOption)
-> Generic ShippingOption
forall x. Rep ShippingOption x -> ShippingOption
forall x. ShippingOption -> Rep ShippingOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShippingOption x -> ShippingOption
$cfrom :: forall x. ShippingOption -> Rep ShippingOption x
Generic, Int -> ShippingOption -> ShowS
[ShippingOption] -> ShowS
ShippingOption -> String
(Int -> ShippingOption -> ShowS)
-> (ShippingOption -> String)
-> ([ShippingOption] -> ShowS)
-> Show ShippingOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShippingOption] -> ShowS
$cshowList :: [ShippingOption] -> ShowS
show :: ShippingOption -> String
$cshow :: ShippingOption -> String
showsPrec :: Int -> ShippingOption -> ShowS
$cshowsPrec :: Int -> ShippingOption -> ShowS
Show)
newtype ShippingOptionId = ShippingOptionId Text
deriving (ShippingOptionId -> ShippingOptionId -> Bool
(ShippingOptionId -> ShippingOptionId -> Bool)
-> (ShippingOptionId -> ShippingOptionId -> Bool)
-> Eq ShippingOptionId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShippingOptionId -> ShippingOptionId -> Bool
$c/= :: ShippingOptionId -> ShippingOptionId -> Bool
== :: ShippingOptionId -> ShippingOptionId -> Bool
$c== :: ShippingOptionId -> ShippingOptionId -> Bool
Eq, Int -> ShippingOptionId -> ShowS
[ShippingOptionId] -> ShowS
ShippingOptionId -> String
(Int -> ShippingOptionId -> ShowS)
-> (ShippingOptionId -> String)
-> ([ShippingOptionId] -> ShowS)
-> Show ShippingOptionId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShippingOptionId] -> ShowS
$cshowList :: [ShippingOptionId] -> ShowS
show :: ShippingOptionId -> String
$cshow :: ShippingOptionId -> String
showsPrec :: Int -> ShippingOptionId -> ShowS
$cshowsPrec :: Int -> ShippingOptionId -> ShowS
Show, (forall x. ShippingOptionId -> Rep ShippingOptionId x)
-> (forall x. Rep ShippingOptionId x -> ShippingOptionId)
-> Generic ShippingOptionId
forall x. Rep ShippingOptionId x -> ShippingOptionId
forall x. ShippingOptionId -> Rep ShippingOptionId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShippingOptionId x -> ShippingOptionId
$cfrom :: forall x. ShippingOptionId -> Rep ShippingOptionId x
Generic, [ShippingOptionId] -> Encoding
[ShippingOptionId] -> Value
ShippingOptionId -> Encoding
ShippingOptionId -> Value
(ShippingOptionId -> Value)
-> (ShippingOptionId -> Encoding)
-> ([ShippingOptionId] -> Value)
-> ([ShippingOptionId] -> Encoding)
-> ToJSON ShippingOptionId
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [ShippingOptionId] -> Encoding
$ctoEncodingList :: [ShippingOptionId] -> Encoding
toJSONList :: [ShippingOptionId] -> Value
$ctoJSONList :: [ShippingOptionId] -> Value
toEncoding :: ShippingOptionId -> Encoding
$ctoEncoding :: ShippingOptionId -> Encoding
toJSON :: ShippingOptionId -> Value
$ctoJSON :: ShippingOptionId -> Value
ToJSON, Value -> Parser [ShippingOptionId]
Value -> Parser ShippingOptionId
(Value -> Parser ShippingOptionId)
-> (Value -> Parser [ShippingOptionId])
-> FromJSON ShippingOptionId
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [ShippingOptionId]
$cparseJSONList :: Value -> Parser [ShippingOptionId]
parseJSON :: Value -> Parser ShippingOptionId
$cparseJSON :: Value -> Parser ShippingOptionId
FromJSON)
data SuccessfulPayment = SuccessfulPayment
{ SuccessfulPayment -> Text
successfulPaymentCurrency :: Text
, SuccessfulPayment -> Int
successfulPaymentTotalAmount :: Int
, SuccessfulPayment -> Text
successfulPaymentInvoicePayload :: Text
, SuccessfulPayment -> Maybe ShippingOptionId
successfulPaymentShippingOptionId :: Maybe ShippingOptionId
, SuccessfulPayment -> Maybe OrderInfo
successfulPaymentOrderInfo :: Maybe OrderInfo
, SuccessfulPayment -> Text
successfulPaymentTelegramPaymentChargeId :: Text
, SuccessfulPayment -> Text
successfulPaymentProviderPaymentChargeId :: Text
}
deriving ((forall x. SuccessfulPayment -> Rep SuccessfulPayment x)
-> (forall x. Rep SuccessfulPayment x -> SuccessfulPayment)
-> Generic SuccessfulPayment
forall x. Rep SuccessfulPayment x -> SuccessfulPayment
forall x. SuccessfulPayment -> Rep SuccessfulPayment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SuccessfulPayment x -> SuccessfulPayment
$cfrom :: forall x. SuccessfulPayment -> Rep SuccessfulPayment x
Generic, Int -> SuccessfulPayment -> ShowS
[SuccessfulPayment] -> ShowS
SuccessfulPayment -> String
(Int -> SuccessfulPayment -> ShowS)
-> (SuccessfulPayment -> String)
-> ([SuccessfulPayment] -> ShowS)
-> Show SuccessfulPayment
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SuccessfulPayment] -> ShowS
$cshowList :: [SuccessfulPayment] -> ShowS
show :: SuccessfulPayment -> String
$cshow :: SuccessfulPayment -> String
showsPrec :: Int -> SuccessfulPayment -> ShowS
$cshowsPrec :: Int -> SuccessfulPayment -> ShowS
Show)
data ShippingQuery = ShippingQuery
{ ShippingQuery -> Text
shippingQueryId :: Text
, ShippingQuery -> User
shippingQueryFrom :: User
, ShippingQuery -> Text
shippingQueryInvoicePayload :: Text
, ShippingQuery -> ShippingAddress
shippingQueryShippingAddress :: ShippingAddress
}
deriving ((forall x. ShippingQuery -> Rep ShippingQuery x)
-> (forall x. Rep ShippingQuery x -> ShippingQuery)
-> Generic ShippingQuery
forall x. Rep ShippingQuery x -> ShippingQuery
forall x. ShippingQuery -> Rep ShippingQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShippingQuery x -> ShippingQuery
$cfrom :: forall x. ShippingQuery -> Rep ShippingQuery x
Generic, Int -> ShippingQuery -> ShowS
[ShippingQuery] -> ShowS
ShippingQuery -> String
(Int -> ShippingQuery -> ShowS)
-> (ShippingQuery -> String)
-> ([ShippingQuery] -> ShowS)
-> Show ShippingQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShippingQuery] -> ShowS
$cshowList :: [ShippingQuery] -> ShowS
show :: ShippingQuery -> String
$cshow :: ShippingQuery -> String
showsPrec :: Int -> ShippingQuery -> ShowS
$cshowsPrec :: Int -> ShippingQuery -> ShowS
Show)
data PreCheckoutQuery = PreCheckoutQuery
{ PreCheckoutQuery -> Text
preCheckoutQueryId :: Text
, PreCheckoutQuery -> User
preCheckoutQueryFrom :: User
, PreCheckoutQuery -> Text
preCheckoutQueryCurrency :: Text
, PreCheckoutQuery -> Int
preCheckoutQueryTotalAmount :: Int
, PreCheckoutQuery -> Text
preCheckoutQueryInvoicePayload :: Text
, PreCheckoutQuery -> Maybe ShippingOptionId
preCheckoutQueryShippingOptionId :: Maybe ShippingOptionId
, PreCheckoutQuery -> Maybe OrderInfo
preCheckoutQueryOrderInfo :: Maybe OrderInfo
}
deriving ((forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x)
-> (forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery)
-> Generic PreCheckoutQuery
forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery
forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PreCheckoutQuery x -> PreCheckoutQuery
$cfrom :: forall x. PreCheckoutQuery -> Rep PreCheckoutQuery x
Generic, Int -> PreCheckoutQuery -> ShowS
[PreCheckoutQuery] -> ShowS
PreCheckoutQuery -> String
(Int -> PreCheckoutQuery -> ShowS)
-> (PreCheckoutQuery -> String)
-> ([PreCheckoutQuery] -> ShowS)
-> Show PreCheckoutQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PreCheckoutQuery] -> ShowS
$cshowList :: [PreCheckoutQuery] -> ShowS
show :: PreCheckoutQuery -> String
$cshow :: PreCheckoutQuery -> String
showsPrec :: Int -> PreCheckoutQuery -> ShowS
$cshowsPrec :: Int -> PreCheckoutQuery -> ShowS
Show)
data PassportData = PassportData
{ PassportData -> [EncryptedPassportElement]
passportDataData :: [EncryptedPassportElement]
, PassportData -> EncryptedCredentials
passportDataCredentials :: EncryptedCredentials
}
deriving ((forall x. PassportData -> Rep PassportData x)
-> (forall x. Rep PassportData x -> PassportData)
-> Generic PassportData
forall x. Rep PassportData x -> PassportData
forall x. PassportData -> Rep PassportData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportData x -> PassportData
$cfrom :: forall x. PassportData -> Rep PassportData x
Generic, Int -> PassportData -> ShowS
[PassportData] -> ShowS
PassportData -> String
(Int -> PassportData -> ShowS)
-> (PassportData -> String)
-> ([PassportData] -> ShowS)
-> Show PassportData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportData] -> ShowS
$cshowList :: [PassportData] -> ShowS
show :: PassportData -> String
$cshow :: PassportData -> String
showsPrec :: Int -> PassportData -> ShowS
$cshowsPrec :: Int -> PassportData -> ShowS
Show)
data PassportFile = PassportFile
{ PassportFile -> FileId
passportFileFileId :: FileId
, PassportFile -> FileId
passportFileFileUniqueId :: FileId
, PassportFile -> Int
passportFileFileSize :: Int
, PassportFile -> POSIXTime
passportFileFileDate :: POSIXTime
}
deriving ((forall x. PassportFile -> Rep PassportFile x)
-> (forall x. Rep PassportFile x -> PassportFile)
-> Generic PassportFile
forall x. Rep PassportFile x -> PassportFile
forall x. PassportFile -> Rep PassportFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportFile x -> PassportFile
$cfrom :: forall x. PassportFile -> Rep PassportFile x
Generic, Int -> PassportFile -> ShowS
[PassportFile] -> ShowS
PassportFile -> String
(Int -> PassportFile -> ShowS)
-> (PassportFile -> String)
-> ([PassportFile] -> ShowS)
-> Show PassportFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportFile] -> ShowS
$cshowList :: [PassportFile] -> ShowS
show :: PassportFile -> String
$cshow :: PassportFile -> String
showsPrec :: Int -> PassportFile -> ShowS
$cshowsPrec :: Int -> PassportFile -> ShowS
Show)
data EncryptedPassportElement = EncryptedPassportElement
{ EncryptedPassportElement -> PassportElementType
encryptedPassportElementType :: PassportElementType
, EncryptedPassportElement -> Maybe Text
encryptedPassportElementData :: Maybe Text
, EncryptedPassportElement -> Maybe Text
encryptedPassportElementPhoneNumber :: Maybe Text
, EncryptedPassportElement -> Maybe Text
encryptedPassportElementEmail :: Maybe Text
, EncryptedPassportElement -> Maybe [PassportFile]
encryptedPassportElementFiles :: Maybe [PassportFile]
, EncryptedPassportElement -> Maybe PassportFile
encryptedPassportElementFrontSide :: Maybe PassportFile
, EncryptedPassportElement -> Maybe PassportFile
encryptedPassportElementReverseSide :: Maybe PassportFile
, EncryptedPassportElement -> Maybe PassportFile
encryptedPassportElementSelfie :: Maybe PassportFile
, EncryptedPassportElement -> Maybe [PassportFile]
encryptedPassportElementTranslation :: Maybe [PassportFile]
, EncryptedPassportElement -> Text
encryptedPassportElementHash :: Text
} deriving ((forall x.
EncryptedPassportElement -> Rep EncryptedPassportElement x)
-> (forall x.
Rep EncryptedPassportElement x -> EncryptedPassportElement)
-> Generic EncryptedPassportElement
forall x.
Rep EncryptedPassportElement x -> EncryptedPassportElement
forall x.
EncryptedPassportElement -> Rep EncryptedPassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EncryptedPassportElement x -> EncryptedPassportElement
$cfrom :: forall x.
EncryptedPassportElement -> Rep EncryptedPassportElement x
Generic, Int -> EncryptedPassportElement -> ShowS
[EncryptedPassportElement] -> ShowS
EncryptedPassportElement -> String
(Int -> EncryptedPassportElement -> ShowS)
-> (EncryptedPassportElement -> String)
-> ([EncryptedPassportElement] -> ShowS)
-> Show EncryptedPassportElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncryptedPassportElement] -> ShowS
$cshowList :: [EncryptedPassportElement] -> ShowS
show :: EncryptedPassportElement -> String
$cshow :: EncryptedPassportElement -> String
showsPrec :: Int -> EncryptedPassportElement -> ShowS
$cshowsPrec :: Int -> EncryptedPassportElement -> ShowS
Show)
data PassportElementType
= PassportElementTypePersonalDetails
| PassportElementTypePassport
| PassportElementTypeDriverLicense
| PassportElementTypeIdentityCard
| PassportElementTypeInternalPassport
| PassportElementTypeAddress
| PassportElementTypeUtilityBill
| PassportElementTypeBankStatement
| PassportElementTypeRentalAgreement
| PassportElementTypePassportRegistration
| PassportElementTypeTemporaryRegistration
| PassportElementTypePhoneNumber
| PassportElementTypeEmail
deriving ((forall x. PassportElementType -> Rep PassportElementType x)
-> (forall x. Rep PassportElementType x -> PassportElementType)
-> Generic PassportElementType
forall x. Rep PassportElementType x -> PassportElementType
forall x. PassportElementType -> Rep PassportElementType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportElementType x -> PassportElementType
$cfrom :: forall x. PassportElementType -> Rep PassportElementType x
Generic, Int -> PassportElementType -> ShowS
[PassportElementType] -> ShowS
PassportElementType -> String
(Int -> PassportElementType -> ShowS)
-> (PassportElementType -> String)
-> ([PassportElementType] -> ShowS)
-> Show PassportElementType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementType] -> ShowS
$cshowList :: [PassportElementType] -> ShowS
show :: PassportElementType -> String
$cshow :: PassportElementType -> String
showsPrec :: Int -> PassportElementType -> ShowS
$cshowsPrec :: Int -> PassportElementType -> ShowS
Show)
data EncryptedCredentials = EncryptedCredentials
{ EncryptedCredentials -> Text
encryptedCredentialsData :: Text
, EncryptedCredentials -> Text
encryptedCredentialsHash :: Text
, EncryptedCredentials -> Text
encryptedCredentialsSecret :: Text
}
deriving ((forall x. EncryptedCredentials -> Rep EncryptedCredentials x)
-> (forall x. Rep EncryptedCredentials x -> EncryptedCredentials)
-> Generic EncryptedCredentials
forall x. Rep EncryptedCredentials x -> EncryptedCredentials
forall x. EncryptedCredentials -> Rep EncryptedCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EncryptedCredentials x -> EncryptedCredentials
$cfrom :: forall x. EncryptedCredentials -> Rep EncryptedCredentials x
Generic, Int -> EncryptedCredentials -> ShowS
[EncryptedCredentials] -> ShowS
EncryptedCredentials -> String
(Int -> EncryptedCredentials -> ShowS)
-> (EncryptedCredentials -> String)
-> ([EncryptedCredentials] -> ShowS)
-> Show EncryptedCredentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncryptedCredentials] -> ShowS
$cshowList :: [EncryptedCredentials] -> ShowS
show :: EncryptedCredentials -> String
$cshow :: EncryptedCredentials -> String
showsPrec :: Int -> EncryptedCredentials -> ShowS
$cshowsPrec :: Int -> EncryptedCredentials -> ShowS
Show)
data PassportErrorSource
= PassportErrorSourceData
| PassportErrorSourceFrontSide
| PassportErrorSourceReverseSide
| PassportErrorSourceSelfie
| PassportErrorSourceFile
| PassportErrorSourceFiles
| PassportErrorSourceTranslationFile
| PassportErrorSourceTranslationFiles
| PassportErrorSourceUnspecified
deriving ((forall x. PassportErrorSource -> Rep PassportErrorSource x)
-> (forall x. Rep PassportErrorSource x -> PassportErrorSource)
-> Generic PassportErrorSource
forall x. Rep PassportErrorSource x -> PassportErrorSource
forall x. PassportErrorSource -> Rep PassportErrorSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportErrorSource x -> PassportErrorSource
$cfrom :: forall x. PassportErrorSource -> Rep PassportErrorSource x
Generic, Int -> PassportErrorSource -> ShowS
[PassportErrorSource] -> ShowS
PassportErrorSource -> String
(Int -> PassportErrorSource -> ShowS)
-> (PassportErrorSource -> String)
-> ([PassportErrorSource] -> ShowS)
-> Show PassportErrorSource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportErrorSource] -> ShowS
$cshowList :: [PassportErrorSource] -> ShowS
show :: PassportErrorSource -> String
$cshow :: PassportErrorSource -> String
showsPrec :: Int -> PassportErrorSource -> ShowS
$cshowsPrec :: Int -> PassportErrorSource -> ShowS
Show)
data PassportElementError
= PassportElementError
{ PassportElementError -> PassportErrorSource
passportElementErroSource :: PassportErrorSource
, PassportElementError -> PassportElementType
passportElementErrorType :: PassportElementType
, PassportElementError -> Text
passportElementErrorName :: Text
, PassportElementError -> Maybe Text
passportElementErrorHash :: Maybe Text
, PassportElementError -> Text
passportElementErrorMessage :: Text
, PassportElementError -> Maybe Text
passportElementErrorFileHash :: Maybe Text
, PassportElementError -> Maybe [Text]
passportElementErrorFileHashes :: Maybe [Text]
, PassportElementError -> Maybe Text
passportElementErrorElementHash :: Maybe Text
}
deriving ((forall x. PassportElementError -> Rep PassportElementError x)
-> (forall x. Rep PassportElementError x -> PassportElementError)
-> Generic PassportElementError
forall x. Rep PassportElementError x -> PassportElementError
forall x. PassportElementError -> Rep PassportElementError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportElementError x -> PassportElementError
$cfrom :: forall x. PassportElementError -> Rep PassportElementError x
Generic, Int -> PassportElementError -> ShowS
[PassportElementError] -> ShowS
PassportElementError -> String
(Int -> PassportElementError -> ShowS)
-> (PassportElementError -> String)
-> ([PassportElementError] -> ShowS)
-> Show PassportElementError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementError] -> ShowS
$cshowList :: [PassportElementError] -> ShowS
show :: PassportElementError -> String
$cshow :: PassportElementError -> String
showsPrec :: Int -> PassportElementError -> ShowS
$cshowsPrec :: Int -> PassportElementError -> ShowS
Show)
data Game = Game
{ Game -> Text
gameTitle :: Text
, Game -> Text
gameDescription :: Text
, Game -> [PhotoSize]
gamePhoto :: [PhotoSize]
, Game -> Maybe Text
gameText :: Maybe Text
, Game -> Maybe [MessageEntity]
gameTextEntities :: Maybe [MessageEntity]
, Game -> Maybe Animation
gameAnimation :: Maybe Animation
}
deriving ((forall x. Game -> Rep Game x)
-> (forall x. Rep Game x -> Game) -> Generic Game
forall x. Rep Game x -> Game
forall x. Game -> Rep Game x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Game x -> Game
$cfrom :: forall x. Game -> Rep Game x
Generic, Int -> Game -> ShowS
[Game] -> ShowS
Game -> String
(Int -> Game -> ShowS)
-> (Game -> String) -> ([Game] -> ShowS) -> Show Game
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Game] -> ShowS
$cshowList :: [Game] -> ShowS
show :: Game -> String
$cshow :: Game -> String
showsPrec :: Int -> Game -> ShowS
$cshowsPrec :: Int -> Game -> ShowS
Show)
newtype CallbackGame = CallbackGame Object
deriving ((forall x. CallbackGame -> Rep CallbackGame x)
-> (forall x. Rep CallbackGame x -> CallbackGame)
-> Generic CallbackGame
forall x. Rep CallbackGame x -> CallbackGame
forall x. CallbackGame -> Rep CallbackGame x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallbackGame x -> CallbackGame
$cfrom :: forall x. CallbackGame -> Rep CallbackGame x
Generic, Int -> CallbackGame -> ShowS
[CallbackGame] -> ShowS
CallbackGame -> String
(Int -> CallbackGame -> ShowS)
-> (CallbackGame -> String)
-> ([CallbackGame] -> ShowS)
-> Show CallbackGame
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallbackGame] -> ShowS
$cshowList :: [CallbackGame] -> ShowS
show :: CallbackGame -> String
$cshow :: CallbackGame -> String
showsPrec :: Int -> CallbackGame -> ShowS
$cshowsPrec :: Int -> CallbackGame -> ShowS
Show)
data GameHighScore = GameHighScore
{ GameHighScore -> Int
gameHighScorePosition :: Int
, GameHighScore -> User
gameHighScoreUser :: User
, GameHighScore -> Int
gameHighScoreScore :: Int
}
deriving ((forall x. GameHighScore -> Rep GameHighScore x)
-> (forall x. Rep GameHighScore x -> GameHighScore)
-> Generic GameHighScore
forall x. Rep GameHighScore x -> GameHighScore
forall x. GameHighScore -> Rep GameHighScore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GameHighScore x -> GameHighScore
$cfrom :: forall x. GameHighScore -> Rep GameHighScore x
Generic, Int -> GameHighScore -> ShowS
[GameHighScore] -> ShowS
GameHighScore -> String
(Int -> GameHighScore -> ShowS)
-> (GameHighScore -> String)
-> ([GameHighScore] -> ShowS)
-> Show GameHighScore
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GameHighScore] -> ShowS
$cshowList :: [GameHighScore] -> ShowS
show :: GameHighScore -> String
$cshow :: GameHighScore -> String
showsPrec :: Int -> GameHighScore -> ShowS
$cshowsPrec :: Int -> GameHighScore -> ShowS
Show)
data CopyMessageId = CopyMessageId
{ CopyMessageId -> MessageId
copyMessageIdMessageId :: MessageId
}
deriving ((forall x. CopyMessageId -> Rep CopyMessageId x)
-> (forall x. Rep CopyMessageId x -> CopyMessageId)
-> Generic CopyMessageId
forall x. Rep CopyMessageId x -> CopyMessageId
forall x. CopyMessageId -> Rep CopyMessageId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyMessageId x -> CopyMessageId
$cfrom :: forall x. CopyMessageId -> Rep CopyMessageId x
Generic, Int -> CopyMessageId -> ShowS
[CopyMessageId] -> ShowS
CopyMessageId -> String
(Int -> CopyMessageId -> ShowS)
-> (CopyMessageId -> String)
-> ([CopyMessageId] -> ShowS)
-> Show CopyMessageId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyMessageId] -> ShowS
$cshowList :: [CopyMessageId] -> ShowS
show :: CopyMessageId -> String
$cshow :: CopyMessageId -> String
showsPrec :: Int -> CopyMessageId -> ShowS
$cshowsPrec :: Int -> CopyMessageId -> ShowS
Show)
data SomeChatId
= SomeChatId ChatId
| SomeChatUsername Text
deriving ((forall x. SomeChatId -> Rep SomeChatId x)
-> (forall x. Rep SomeChatId x -> SomeChatId) -> Generic SomeChatId
forall x. Rep SomeChatId x -> SomeChatId
forall x. SomeChatId -> Rep SomeChatId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SomeChatId x -> SomeChatId
$cfrom :: forall x. SomeChatId -> Rep SomeChatId x
Generic)
instance ToJSON SomeChatId where toJSON :: SomeChatId -> Value
toJSON = SomeChatId -> Value
forall a. (Generic a, GSomeJSON (Rep a)) => a -> Value
genericSomeToJSON
instance FromJSON SomeChatId where parseJSON :: Value -> Parser SomeChatId
parseJSON = Value -> Parser SomeChatId
forall a. (Generic a, GSomeJSON (Rep a)) => Value -> Parser a
genericSomeParseJSON
instance ToHttpApiData SomeChatId where
toUrlPiece :: SomeChatId -> Text
toUrlPiece (SomeChatId ChatId
chatid) = ChatId -> Text
forall a. ToHttpApiData a => a -> Text
toUrlPiece ChatId
chatid
toUrlPiece (SomeChatUsername Text
name) = Text
name
data BotCommand = BotCommand
{ BotCommand -> Text
botCommandCommand :: Text
, BotCommand -> Text
botCommandDescription :: Text
}
deriving ((forall x. BotCommand -> Rep BotCommand x)
-> (forall x. Rep BotCommand x -> BotCommand) -> Generic BotCommand
forall x. Rep BotCommand x -> BotCommand
forall x. BotCommand -> Rep BotCommand x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BotCommand x -> BotCommand
$cfrom :: forall x. BotCommand -> Rep BotCommand x
Generic, Int -> BotCommand -> ShowS
[BotCommand] -> ShowS
BotCommand -> String
(Int -> BotCommand -> ShowS)
-> (BotCommand -> String)
-> ([BotCommand] -> ShowS)
-> Show BotCommand
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BotCommand] -> ShowS
$cshowList :: [BotCommand] -> ShowS
show :: BotCommand -> String
$cshow :: BotCommand -> String
showsPrec :: Int -> BotCommand -> ShowS
$cshowsPrec :: Int -> BotCommand -> ShowS
Show)
data BotCommandScope
= BotCommandScopeDefault
| BotCommandScopeAllPrivateChats
| BotCommandScopeAllGroupChats
| BotCommandScopeAllChatAdministrators
| BotCommandScopeChat SomeChatId
| BotCommandScopeChatAdministrators SomeChatId
| BotCommandScopeChatMember SomeChatId UserId
addType :: Text -> [Pair] -> [Pair]
addType :: Text -> [Pair] -> [Pair]
addType Text
name [Pair]
xs = (Key
"type" Key -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= Text
name) Pair -> [Pair] -> [Pair]
forall a. a -> [a] -> [a]
: [Pair]
xs
instance ToJSON BotCommandScope where
toJSON :: BotCommandScope -> Value
toJSON = \case
BotCommandScope
BotCommandScopeDefault ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"default" []
BotCommandScope
BotCommandScopeAllPrivateChats ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"all_private_chats" []
BotCommandScope
BotCommandScopeAllGroupChats ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"all_group_chats" []
BotCommandScope
BotCommandScopeAllChatAdministrators ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"all_chat_administrators" []
BotCommandScopeChat SomeChatId
sci ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"chat" [Key
"chat_id" Key -> SomeChatId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SomeChatId
sci]
BotCommandScopeChatAdministrators SomeChatId
sci ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"chat_administrators" [Key
"chat_id" Key -> SomeChatId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SomeChatId
sci]
BotCommandScopeChatMember SomeChatId
sci UserId
ui ->
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$ Text -> [Pair] -> [Pair]
addType Text
"chat_member" [Key
"chat_id" Key -> SomeChatId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= SomeChatId
sci, Key
"user_id" Key -> UserId -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= UserId
ui]
instance FromJSON BotCommandScope where
parseJSON :: Value -> Parser BotCommandScope
parseJSON = String
-> (Object -> Parser BotCommandScope)
-> Value
-> Parser BotCommandScope
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"BotCommandScope" \Object
o ->
(Object
o Object -> Key -> Parser Text
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type" :: Parser Text) Parser Text
-> (Text -> Parser BotCommandScope) -> Parser BotCommandScope
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Text
"default" -> BotCommandScope -> Parser BotCommandScope
forall (f :: * -> *) a. Applicative f => a -> f a
pure BotCommandScope
BotCommandScopeDefault
Text
"all_private_chats" -> BotCommandScope -> Parser BotCommandScope
forall (f :: * -> *) a. Applicative f => a -> f a
pure BotCommandScope
BotCommandScopeAllPrivateChats
Text
"all_group_chats" -> BotCommandScope -> Parser BotCommandScope
forall (f :: * -> *) a. Applicative f => a -> f a
pure BotCommandScope
BotCommandScopeAllGroupChats
Text
"all_chat_administrators"-> BotCommandScope -> Parser BotCommandScope
forall (f :: * -> *) a. Applicative f => a -> f a
pure BotCommandScope
BotCommandScopeAllChatAdministrators
Text
"chat" -> SomeChatId -> BotCommandScope
BotCommandScopeChat (SomeChatId -> BotCommandScope)
-> Parser SomeChatId -> Parser BotCommandScope
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SomeChatId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"chat_id"
Text
"chat_administrators"-> SomeChatId -> BotCommandScope
BotCommandScopeChatAdministrators (SomeChatId -> BotCommandScope)
-> Parser SomeChatId -> Parser BotCommandScope
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SomeChatId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"chat_id"
Text
"chat_member"-> SomeChatId -> UserId -> BotCommandScope
BotCommandScopeChatMember (SomeChatId -> UserId -> BotCommandScope)
-> Parser SomeChatId -> Parser (UserId -> BotCommandScope)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
o Object -> Key -> Parser SomeChatId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"chat_id" Parser (UserId -> BotCommandScope)
-> Parser UserId -> Parser BotCommandScope
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
o Object -> Key -> Parser UserId
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"user_id"
Text
t -> String -> Parser BotCommandScope
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser BotCommandScope)
-> String -> Parser BotCommandScope
forall a b. (a -> b) -> a -> b
$ Text -> String
Text.unpack (Text
"Unknown type: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t)
data InputMediaGeneric = InputMediaGeneric
{ InputMediaGeneric -> InputFile
inputMediaGenericMedia :: InputFile
, InputMediaGeneric -> Maybe Text
inputMediaGenericCaption :: Maybe Text
, InputMediaGeneric -> Maybe Text
inputMediaGenericParseMode :: Maybe Text
, InputMediaGeneric -> Maybe [MessageEntity]
inputMediaGenericCaptionEntities :: Maybe [MessageEntity]
}
deriving (forall x. InputMediaGeneric -> Rep InputMediaGeneric x)
-> (forall x. Rep InputMediaGeneric x -> InputMediaGeneric)
-> Generic InputMediaGeneric
forall x. Rep InputMediaGeneric x -> InputMediaGeneric
forall x. InputMediaGeneric -> Rep InputMediaGeneric x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputMediaGeneric x -> InputMediaGeneric
$cfrom :: forall x. InputMediaGeneric -> Rep InputMediaGeneric x
Generic
data InputMediaGenericThumb = InputMediaGenericThumb
{ InputMediaGenericThumb -> InputMediaGeneric
inputMediaGenericGeneric :: InputMediaGeneric
, InputMediaGenericThumb -> Maybe InputFile
inputMediaGenericThumb :: Maybe InputFile
}
data InputMedia
= InputMediaPhoto InputMediaGeneric
| InputMediaVideo
{ InputMedia -> InputMediaGenericThumb
inputMediaVideoGeneric :: InputMediaGenericThumb
, InputMedia -> Maybe Integer
inputMediaVideoWidth :: Maybe Integer
, InputMedia -> Maybe Integer
inputMediaVideoHeight :: Maybe Integer
, InputMedia -> Maybe Integer
inputMediaVideoDuration :: Maybe Integer
, InputMedia -> Maybe Bool
inputMediaVideoSupportsStreaming :: Maybe Bool
}
| InputMediaAnimation
{ InputMedia -> InputMediaGenericThumb
inputMediaAnimationGeneric :: InputMediaGenericThumb
, InputMedia -> Maybe Integer
inputMediaAnimationWidth :: Maybe Integer
, InputMedia -> Maybe Integer
inputMediaAnimationHeight :: Maybe Integer
, InputMedia -> Maybe Integer
inputMediaAnimationDuration :: Maybe Integer
}
| InputMediaAudio
{ InputMedia -> InputMediaGenericThumb
inputMediaAudioGeneric :: InputMediaGenericThumb
, InputMedia -> Maybe Integer
inputMediaAudioDuration :: Maybe Integer
, InputMedia -> Maybe Text
inputMediaAudioPerformer :: Maybe Text
, InputMedia -> Maybe Text
inputMediaAudioTitle :: Maybe Text
}
| InputMediaDocument
{ InputMedia -> InputMediaGenericThumb
inputMediaDocumentGeneric :: InputMediaGenericThumb
, InputMedia -> Maybe Bool
inputMediaDocumentDisableContentTypeDetection :: Maybe Bool
}