{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TemplateHaskell #-}

-- | TD API data types generated by tdlib-gen
module TDLib.Generated.Types where

import GHC.Generics
import Language.Haskell.Codegen.TH
import Data.ByteString.Base64.Type
import qualified Data.Text as T
import Language.TL.I64

type I53 = Int
type I32 = Int
type T = T.Text

data Error
  = -- | An object of this type can be returned on every function call, in case of an error
  Error
    { -- | Error code; subject to future changes. If the error code is 406, the error message must not be processed in any way and must not be displayed to the user
      Error -> I32
code_1 :: I32,
      -- | Error message; subject to future changes
      Error -> T
message_1 :: T
    }
  deriving (I32 -> Error -> ShowS
[Error] -> ShowS
Error -> String
(I32 -> Error -> ShowS)
-> (Error -> String) -> ([Error] -> ShowS) -> Show Error
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Error] -> ShowS
$cshowList :: [Error] -> ShowS
show :: Error -> String
$cshow :: Error -> String
showsPrec :: I32 -> Error -> ShowS
$cshowsPrec :: I32 -> Error -> ShowS
Show, Error -> Error -> Bool
(Error -> Error -> Bool) -> (Error -> Error -> Bool) -> Eq Error
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Error -> Error -> Bool
$c/= :: Error -> Error -> Bool
== :: Error -> Error -> Bool
$c== :: Error -> Error -> Bool
Eq, (forall x. Error -> Rep Error x)
-> (forall x. Rep Error x -> Error) -> Generic Error
forall x. Rep Error x -> Error
forall x. Error -> Rep Error x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Error x -> Error
$cfrom :: forall x. Error -> Rep Error x
Generic)
data Ok
  = -- | An object of this type is returned on a successful function call for certain functions
  Ok
    { 
    }
  deriving (I32 -> Ok -> ShowS
[Ok] -> ShowS
Ok -> String
(I32 -> Ok -> ShowS)
-> (Ok -> String) -> ([Ok] -> ShowS) -> Show Ok
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ok] -> ShowS
$cshowList :: [Ok] -> ShowS
show :: Ok -> String
$cshow :: Ok -> String
showsPrec :: I32 -> Ok -> ShowS
$cshowsPrec :: I32 -> Ok -> ShowS
Show, Ok -> Ok -> Bool
(Ok -> Ok -> Bool) -> (Ok -> Ok -> Bool) -> Eq Ok
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ok -> Ok -> Bool
$c/= :: Ok -> Ok -> Bool
== :: Ok -> Ok -> Bool
$c== :: Ok -> Ok -> Bool
Eq, (forall x. Ok -> Rep Ok x)
-> (forall x. Rep Ok x -> Ok) -> Generic Ok
forall x. Rep Ok x -> Ok
forall x. Ok -> Rep Ok x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Ok x -> Ok
$cfrom :: forall x. Ok -> Rep Ok x
Generic)
data TdlibParameters
  = -- | Contains parameters for TDLib initialization
  TdlibParameters
    { -- | If set to true, the Telegram test environment will be used instead of the production environment
      TdlibParameters -> Bool
use_test_dc_1 :: Bool,
      -- | The path to the directory for the persistent database; if empty, the current working directory will be used
      TdlibParameters -> T
database_directory_1 :: T,
      -- | The path to the directory for storing files; if empty, database_directory will be used
      TdlibParameters -> T
files_directory_1 :: T,
      -- | If set to true, information about downloaded and uploaded files will be saved between application restarts
      TdlibParameters -> Bool
use_file_database_1 :: Bool,
      -- | If set to true, the library will maintain a cache of users, basic groups, supergroups, channels and secret chats. Implies use_file_database
      TdlibParameters -> Bool
use_chat_info_database_1 :: Bool,
      -- | If set to true, the library will maintain a cache of chats and messages. Implies use_chat_info_database
      TdlibParameters -> Bool
use_message_database_1 :: Bool,
      -- | If set to true, support for secret chats will be enabled
      TdlibParameters -> Bool
use_secret_chats_1 :: Bool,
      -- | Application identifier for Telegram API access, which can be obtained at https://my.telegram.org
      TdlibParameters -> I32
api_id_1 :: I32,
      -- | Application identifier hash for Telegram API access, which can be obtained at https://my.telegram.org
      TdlibParameters -> T
api_hash_1 :: T,
      -- | IETF language tag of the user's operating system language; must be non-empty
      TdlibParameters -> T
system_language_code_1 :: T,
      -- | Model of the device the application is being run on; must be non-empty
      TdlibParameters -> T
device_model_1 :: T,
      -- | Version of the operating system the application is being run on; must be non-empty
      TdlibParameters -> T
system_version_1 :: T,
      -- | Application version; must be non-empty
      TdlibParameters -> T
application_version_1 :: T,
      -- | If set to true, old files will automatically be deleted
      TdlibParameters -> Bool
enable_storage_optimizer_1 :: Bool,
      -- | If set to true, original file names will be ignored. Otherwise, downloaded files will be saved under names as close as possible to the original name
      TdlibParameters -> Bool
ignore_file_names_1 :: Bool
    }
  deriving (I32 -> TdlibParameters -> ShowS
[TdlibParameters] -> ShowS
TdlibParameters -> String
(I32 -> TdlibParameters -> ShowS)
-> (TdlibParameters -> String)
-> ([TdlibParameters] -> ShowS)
-> Show TdlibParameters
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TdlibParameters] -> ShowS
$cshowList :: [TdlibParameters] -> ShowS
show :: TdlibParameters -> String
$cshow :: TdlibParameters -> String
showsPrec :: I32 -> TdlibParameters -> ShowS
$cshowsPrec :: I32 -> TdlibParameters -> ShowS
Show, TdlibParameters -> TdlibParameters -> Bool
(TdlibParameters -> TdlibParameters -> Bool)
-> (TdlibParameters -> TdlibParameters -> Bool)
-> Eq TdlibParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TdlibParameters -> TdlibParameters -> Bool
$c/= :: TdlibParameters -> TdlibParameters -> Bool
== :: TdlibParameters -> TdlibParameters -> Bool
$c== :: TdlibParameters -> TdlibParameters -> Bool
Eq, (forall x. TdlibParameters -> Rep TdlibParameters x)
-> (forall x. Rep TdlibParameters x -> TdlibParameters)
-> Generic TdlibParameters
forall x. Rep TdlibParameters x -> TdlibParameters
forall x. TdlibParameters -> Rep TdlibParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TdlibParameters x -> TdlibParameters
$cfrom :: forall x. TdlibParameters -> Rep TdlibParameters x
Generic)
-- | Provides information about the method by which an authentication code is delivered to the user
data AuthenticationCodeType
  = -- | An authentication code is delivered via a private Telegram message, which can be viewed in another client 
  AuthenticationCodeTypeTelegramMessage
    { -- | Length of the code
      AuthenticationCodeType -> I32
length_1 :: I32
    }
  | -- | An authentication code is delivered via an SMS message to the specified phone number 
  AuthenticationCodeTypeSms
    { -- | Length of the code
      AuthenticationCodeType -> I32
length_2 :: I32
    }
  | -- | An authentication code is delivered via a phone call to the specified phone number 
  AuthenticationCodeTypeCall
    { -- | Length of the code
      AuthenticationCodeType -> I32
length_3 :: I32
    }
  | -- | An authentication code is delivered by an immediately cancelled call to the specified phone number. The number from which the call was made is the code 
  AuthenticationCodeTypeFlashCall
    { -- | Pattern of the phone number from which the call will be made
      AuthenticationCodeType -> T
pattern_4 :: T
    }
  deriving (I32 -> AuthenticationCodeType -> ShowS
[AuthenticationCodeType] -> ShowS
AuthenticationCodeType -> String
(I32 -> AuthenticationCodeType -> ShowS)
-> (AuthenticationCodeType -> String)
-> ([AuthenticationCodeType] -> ShowS)
-> Show AuthenticationCodeType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticationCodeType] -> ShowS
$cshowList :: [AuthenticationCodeType] -> ShowS
show :: AuthenticationCodeType -> String
$cshow :: AuthenticationCodeType -> String
showsPrec :: I32 -> AuthenticationCodeType -> ShowS
$cshowsPrec :: I32 -> AuthenticationCodeType -> ShowS
Show, AuthenticationCodeType -> AuthenticationCodeType -> Bool
(AuthenticationCodeType -> AuthenticationCodeType -> Bool)
-> (AuthenticationCodeType -> AuthenticationCodeType -> Bool)
-> Eq AuthenticationCodeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticationCodeType -> AuthenticationCodeType -> Bool
$c/= :: AuthenticationCodeType -> AuthenticationCodeType -> Bool
== :: AuthenticationCodeType -> AuthenticationCodeType -> Bool
$c== :: AuthenticationCodeType -> AuthenticationCodeType -> Bool
Eq, (forall x. AuthenticationCodeType -> Rep AuthenticationCodeType x)
-> (forall x.
    Rep AuthenticationCodeType x -> AuthenticationCodeType)
-> Generic AuthenticationCodeType
forall x. Rep AuthenticationCodeType x -> AuthenticationCodeType
forall x. AuthenticationCodeType -> Rep AuthenticationCodeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthenticationCodeType x -> AuthenticationCodeType
$cfrom :: forall x. AuthenticationCodeType -> Rep AuthenticationCodeType x
Generic)
data AuthenticationCodeInfo
  = -- | Information about the authentication code that was sent 
  AuthenticationCodeInfo
    { -- | A phone number that is being authenticated 
      AuthenticationCodeInfo -> T
phone_number_1 :: T,
      -- | Describes the way the code was sent to the user 
      AuthenticationCodeInfo -> AuthenticationCodeType
type_1 :: AuthenticationCodeType,
      -- | Describes the way the next code will be sent to the user; may be null 
      AuthenticationCodeInfo -> AuthenticationCodeType
next_type_1 :: AuthenticationCodeType,
      -- | Timeout before the code should be re-sent, in seconds
      AuthenticationCodeInfo -> I32
timeout_1 :: I32
    }
  deriving (I32 -> AuthenticationCodeInfo -> ShowS
[AuthenticationCodeInfo] -> ShowS
AuthenticationCodeInfo -> String
(I32 -> AuthenticationCodeInfo -> ShowS)
-> (AuthenticationCodeInfo -> String)
-> ([AuthenticationCodeInfo] -> ShowS)
-> Show AuthenticationCodeInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthenticationCodeInfo] -> ShowS
$cshowList :: [AuthenticationCodeInfo] -> ShowS
show :: AuthenticationCodeInfo -> String
$cshow :: AuthenticationCodeInfo -> String
showsPrec :: I32 -> AuthenticationCodeInfo -> ShowS
$cshowsPrec :: I32 -> AuthenticationCodeInfo -> ShowS
Show, AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool
(AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool)
-> (AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool)
-> Eq AuthenticationCodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool
$c/= :: AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool
== :: AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool
$c== :: AuthenticationCodeInfo -> AuthenticationCodeInfo -> Bool
Eq, (forall x. AuthenticationCodeInfo -> Rep AuthenticationCodeInfo x)
-> (forall x.
    Rep AuthenticationCodeInfo x -> AuthenticationCodeInfo)
-> Generic AuthenticationCodeInfo
forall x. Rep AuthenticationCodeInfo x -> AuthenticationCodeInfo
forall x. AuthenticationCodeInfo -> Rep AuthenticationCodeInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthenticationCodeInfo x -> AuthenticationCodeInfo
$cfrom :: forall x. AuthenticationCodeInfo -> Rep AuthenticationCodeInfo x
Generic)
data EmailAddressAuthenticationCodeInfo
  = -- | Information about the email address authentication code that was sent 
  EmailAddressAuthenticationCodeInfo
    { -- | Pattern of the email address to which an authentication code was sent 
      EmailAddressAuthenticationCodeInfo -> T
email_address_pattern_1 :: T,
      -- | Length of the code; 0 if unknown
      EmailAddressAuthenticationCodeInfo -> I32
length_1 :: I32
    }
  deriving (I32 -> EmailAddressAuthenticationCodeInfo -> ShowS
[EmailAddressAuthenticationCodeInfo] -> ShowS
EmailAddressAuthenticationCodeInfo -> String
(I32 -> EmailAddressAuthenticationCodeInfo -> ShowS)
-> (EmailAddressAuthenticationCodeInfo -> String)
-> ([EmailAddressAuthenticationCodeInfo] -> ShowS)
-> Show EmailAddressAuthenticationCodeInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EmailAddressAuthenticationCodeInfo] -> ShowS
$cshowList :: [EmailAddressAuthenticationCodeInfo] -> ShowS
show :: EmailAddressAuthenticationCodeInfo -> String
$cshow :: EmailAddressAuthenticationCodeInfo -> String
showsPrec :: I32 -> EmailAddressAuthenticationCodeInfo -> ShowS
$cshowsPrec :: I32 -> EmailAddressAuthenticationCodeInfo -> ShowS
Show, EmailAddressAuthenticationCodeInfo
-> EmailAddressAuthenticationCodeInfo -> Bool
(EmailAddressAuthenticationCodeInfo
 -> EmailAddressAuthenticationCodeInfo -> Bool)
-> (EmailAddressAuthenticationCodeInfo
    -> EmailAddressAuthenticationCodeInfo -> Bool)
-> Eq EmailAddressAuthenticationCodeInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EmailAddressAuthenticationCodeInfo
-> EmailAddressAuthenticationCodeInfo -> Bool
$c/= :: EmailAddressAuthenticationCodeInfo
-> EmailAddressAuthenticationCodeInfo -> Bool
== :: EmailAddressAuthenticationCodeInfo
-> EmailAddressAuthenticationCodeInfo -> Bool
$c== :: EmailAddressAuthenticationCodeInfo
-> EmailAddressAuthenticationCodeInfo -> Bool
Eq, (forall x.
 EmailAddressAuthenticationCodeInfo
 -> Rep EmailAddressAuthenticationCodeInfo x)
-> (forall x.
    Rep EmailAddressAuthenticationCodeInfo x
    -> EmailAddressAuthenticationCodeInfo)
-> Generic EmailAddressAuthenticationCodeInfo
forall x.
Rep EmailAddressAuthenticationCodeInfo x
-> EmailAddressAuthenticationCodeInfo
forall x.
EmailAddressAuthenticationCodeInfo
-> Rep EmailAddressAuthenticationCodeInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EmailAddressAuthenticationCodeInfo x
-> EmailAddressAuthenticationCodeInfo
$cfrom :: forall x.
EmailAddressAuthenticationCodeInfo
-> Rep EmailAddressAuthenticationCodeInfo x
Generic)
data TextEntity
  = -- | Represents a part of the text that needs to be formatted in some unusual way 
  TextEntity
    { -- | Offset of the entity in UTF-16 code units 
      TextEntity -> I32
offset_1 :: I32,
      -- | Length of the entity, in UTF-16 code units 
      TextEntity -> I32
length_1 :: I32,
      -- | Type of the entity
      TextEntity -> TextEntityType
type_1 :: TextEntityType
    }
  deriving (I32 -> TextEntity -> ShowS
[TextEntity] -> ShowS
TextEntity -> String
(I32 -> TextEntity -> ShowS)
-> (TextEntity -> String)
-> ([TextEntity] -> ShowS)
-> Show TextEntity
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEntity] -> ShowS
$cshowList :: [TextEntity] -> ShowS
show :: TextEntity -> String
$cshow :: TextEntity -> String
showsPrec :: I32 -> TextEntity -> ShowS
$cshowsPrec :: I32 -> TextEntity -> ShowS
Show, TextEntity -> TextEntity -> Bool
(TextEntity -> TextEntity -> Bool)
-> (TextEntity -> TextEntity -> Bool) -> Eq TextEntity
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEntity -> TextEntity -> Bool
$c/= :: TextEntity -> TextEntity -> Bool
== :: TextEntity -> TextEntity -> Bool
$c== :: TextEntity -> TextEntity -> Bool
Eq, (forall x. TextEntity -> Rep TextEntity x)
-> (forall x. Rep TextEntity x -> TextEntity) -> Generic TextEntity
forall x. Rep TextEntity x -> TextEntity
forall x. TextEntity -> Rep TextEntity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextEntity x -> TextEntity
$cfrom :: forall x. TextEntity -> Rep TextEntity x
Generic)
data TextEntities
  = -- | Contains a list of text entities 
  TextEntities
    { -- | List of text entities
      TextEntities -> [TextEntity]
entities_1 :: ([]) (TextEntity)
    }
  deriving (I32 -> TextEntities -> ShowS
[TextEntities] -> ShowS
TextEntities -> String
(I32 -> TextEntities -> ShowS)
-> (TextEntities -> String)
-> ([TextEntities] -> ShowS)
-> Show TextEntities
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEntities] -> ShowS
$cshowList :: [TextEntities] -> ShowS
show :: TextEntities -> String
$cshow :: TextEntities -> String
showsPrec :: I32 -> TextEntities -> ShowS
$cshowsPrec :: I32 -> TextEntities -> ShowS
Show, TextEntities -> TextEntities -> Bool
(TextEntities -> TextEntities -> Bool)
-> (TextEntities -> TextEntities -> Bool) -> Eq TextEntities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEntities -> TextEntities -> Bool
$c/= :: TextEntities -> TextEntities -> Bool
== :: TextEntities -> TextEntities -> Bool
$c== :: TextEntities -> TextEntities -> Bool
Eq, (forall x. TextEntities -> Rep TextEntities x)
-> (forall x. Rep TextEntities x -> TextEntities)
-> Generic TextEntities
forall x. Rep TextEntities x -> TextEntities
forall x. TextEntities -> Rep TextEntities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextEntities x -> TextEntities
$cfrom :: forall x. TextEntities -> Rep TextEntities x
Generic)
data FormattedText
  = -- | A text with some entities 
  FormattedText
    { -- | The text 
      FormattedText -> T
text_1 :: T,
      -- | Entities contained in the text. Entities can be nested, but must not mutually intersect with each other.
      FormattedText -> [TextEntity]
entities_1 :: ([]) (TextEntity)
    }
  deriving (I32 -> FormattedText -> ShowS
[FormattedText] -> ShowS
FormattedText -> String
(I32 -> FormattedText -> ShowS)
-> (FormattedText -> String)
-> ([FormattedText] -> ShowS)
-> Show FormattedText
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormattedText] -> ShowS
$cshowList :: [FormattedText] -> ShowS
show :: FormattedText -> String
$cshow :: FormattedText -> String
showsPrec :: I32 -> FormattedText -> ShowS
$cshowsPrec :: I32 -> FormattedText -> ShowS
Show, FormattedText -> FormattedText -> Bool
(FormattedText -> FormattedText -> Bool)
-> (FormattedText -> FormattedText -> Bool) -> Eq FormattedText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormattedText -> FormattedText -> Bool
$c/= :: FormattedText -> FormattedText -> Bool
== :: FormattedText -> FormattedText -> Bool
$c== :: FormattedText -> FormattedText -> Bool
Eq, (forall x. FormattedText -> Rep FormattedText x)
-> (forall x. Rep FormattedText x -> FormattedText)
-> Generic FormattedText
forall x. Rep FormattedText x -> FormattedText
forall x. FormattedText -> Rep FormattedText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormattedText x -> FormattedText
$cfrom :: forall x. FormattedText -> Rep FormattedText x
Generic)
data TermsOfService
  = -- | Contains Telegram terms of service 
  TermsOfService
    { -- | Text of the terms of service 
      TermsOfService -> FormattedText
text_1 :: FormattedText,
      -- | The minimum age of a user to be able to accept the terms; 0 if any 
      TermsOfService -> I32
min_user_age_1 :: I32,
      -- | True, if a blocking popup with terms of service must be shown to the user
      TermsOfService -> Bool
show_popup_1 :: Bool
    }
  deriving (I32 -> TermsOfService -> ShowS
[TermsOfService] -> ShowS
TermsOfService -> String
(I32 -> TermsOfService -> ShowS)
-> (TermsOfService -> String)
-> ([TermsOfService] -> ShowS)
-> Show TermsOfService
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TermsOfService] -> ShowS
$cshowList :: [TermsOfService] -> ShowS
show :: TermsOfService -> String
$cshow :: TermsOfService -> String
showsPrec :: I32 -> TermsOfService -> ShowS
$cshowsPrec :: I32 -> TermsOfService -> ShowS
Show, TermsOfService -> TermsOfService -> Bool
(TermsOfService -> TermsOfService -> Bool)
-> (TermsOfService -> TermsOfService -> Bool) -> Eq TermsOfService
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TermsOfService -> TermsOfService -> Bool
$c/= :: TermsOfService -> TermsOfService -> Bool
== :: TermsOfService -> TermsOfService -> Bool
$c== :: TermsOfService -> TermsOfService -> Bool
Eq, (forall x. TermsOfService -> Rep TermsOfService x)
-> (forall x. Rep TermsOfService x -> TermsOfService)
-> Generic TermsOfService
forall x. Rep TermsOfService x -> TermsOfService
forall x. TermsOfService -> Rep TermsOfService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TermsOfService x -> TermsOfService
$cfrom :: forall x. TermsOfService -> Rep TermsOfService x
Generic)
-- | Represents the current authorization state of the client
data AuthorizationState
  = -- | TDLib needs TdlibParameters for initialization
  AuthorizationStateWaitTdlibParameters
    { 
    }
  | -- | TDLib needs an encryption key to decrypt the local database 
  AuthorizationStateWaitEncryptionKey
    { -- | True, if the database is currently encrypted
      AuthorizationState -> Bool
is_encrypted_2 :: Bool
    }
  | -- | TDLib needs the user's phone number to authorize. Call `setAuthenticationPhoneNumber` to provide the phone number, or use `requestQrCodeAuthentication`, or `checkAuthenticationBotToken` for other authentication options
  AuthorizationStateWaitPhoneNumber
    { 
    }
  | -- | TDLib needs the user's authentication code to authorize 
  AuthorizationStateWaitCode
    { -- | Information about the authorization code that was sent
      AuthorizationState -> AuthenticationCodeInfo
code_info_4 :: AuthenticationCodeInfo
    }
  | -- | The user needs to confirm authorization on another logged in device by scanning a QR code with the provided link 
  AuthorizationStateWaitOtherDeviceConfirmation
    { -- | A tg:// URL for the QR code. The link will be updated frequently
      AuthorizationState -> T
link_5 :: T
    }
  | -- | The user is unregistered and need to accept terms of service and enter their first name and last name to finish registration 
  AuthorizationStateWaitRegistration
    { -- | Telegram terms of service
      AuthorizationState -> TermsOfService
terms_of_service_6 :: TermsOfService
    }
  | -- | The user has been authorized, but needs to enter a password to start using the application 
  AuthorizationStateWaitPassword
    { -- | Hint for the password; may be empty 
      AuthorizationState -> T
password_hint_7 :: T,
      -- | True, if a recovery email address has been set up
      AuthorizationState -> Bool
has_recovery_email_address_7 :: Bool,
      -- | Pattern of the email address to which the recovery email was sent; empty until a recovery email has been sent
      AuthorizationState -> T
recovery_email_address_pattern_7 :: T
    }
  | -- | The user has been successfully authorized. TDLib is now ready to answer queries
  AuthorizationStateReady
    { 
    }
  | -- | The user is currently logging out
  AuthorizationStateLoggingOut
    { 
    }
  | -- | TDLib is closing, all subsequent queries will be answered with the error 500. Note that closing TDLib can take a while. All resources will be freed only after authorizationStateClosed has been received
  AuthorizationStateClosing
    { 
    }
  | -- | TDLib client is in its final state. All databases are closed and all resources are released. No other updates will be received after this. All queries will be responded to
  AuthorizationStateClosed
    { 
    }
  deriving (I32 -> AuthorizationState -> ShowS
[AuthorizationState] -> ShowS
AuthorizationState -> String
(I32 -> AuthorizationState -> ShowS)
-> (AuthorizationState -> String)
-> ([AuthorizationState] -> ShowS)
-> Show AuthorizationState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AuthorizationState] -> ShowS
$cshowList :: [AuthorizationState] -> ShowS
show :: AuthorizationState -> String
$cshow :: AuthorizationState -> String
showsPrec :: I32 -> AuthorizationState -> ShowS
$cshowsPrec :: I32 -> AuthorizationState -> ShowS
Show, AuthorizationState -> AuthorizationState -> Bool
(AuthorizationState -> AuthorizationState -> Bool)
-> (AuthorizationState -> AuthorizationState -> Bool)
-> Eq AuthorizationState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AuthorizationState -> AuthorizationState -> Bool
$c/= :: AuthorizationState -> AuthorizationState -> Bool
== :: AuthorizationState -> AuthorizationState -> Bool
$c== :: AuthorizationState -> AuthorizationState -> Bool
Eq, (forall x. AuthorizationState -> Rep AuthorizationState x)
-> (forall x. Rep AuthorizationState x -> AuthorizationState)
-> Generic AuthorizationState
forall x. Rep AuthorizationState x -> AuthorizationState
forall x. AuthorizationState -> Rep AuthorizationState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AuthorizationState x -> AuthorizationState
$cfrom :: forall x. AuthorizationState -> Rep AuthorizationState x
Generic)
data PasswordState
  = -- | Represents the current state of 2-step verification 
  PasswordState
    { -- | True, if a 2-step verification password is set 
      PasswordState -> Bool
has_password_1 :: Bool,
      -- | Hint for the password; may be empty
      PasswordState -> T
password_hint_1 :: T,
      -- | True, if a recovery email is set 
      PasswordState -> Bool
has_recovery_email_address_1 :: Bool,
      -- | True, if some Telegram Passport elements were saved
      PasswordState -> Bool
has_passport_data_1 :: Bool,
      -- | Information about the recovery email address to which the confirmation email was sent; may be null
      PasswordState -> EmailAddressAuthenticationCodeInfo
recovery_email_address_code_info_1 :: EmailAddressAuthenticationCodeInfo
    }
  deriving (I32 -> PasswordState -> ShowS
[PasswordState] -> ShowS
PasswordState -> String
(I32 -> PasswordState -> ShowS)
-> (PasswordState -> String)
-> ([PasswordState] -> ShowS)
-> Show PasswordState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PasswordState] -> ShowS
$cshowList :: [PasswordState] -> ShowS
show :: PasswordState -> String
$cshow :: PasswordState -> String
showsPrec :: I32 -> PasswordState -> ShowS
$cshowsPrec :: I32 -> PasswordState -> ShowS
Show, PasswordState -> PasswordState -> Bool
(PasswordState -> PasswordState -> Bool)
-> (PasswordState -> PasswordState -> Bool) -> Eq PasswordState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PasswordState -> PasswordState -> Bool
$c/= :: PasswordState -> PasswordState -> Bool
== :: PasswordState -> PasswordState -> Bool
$c== :: PasswordState -> PasswordState -> Bool
Eq, (forall x. PasswordState -> Rep PasswordState x)
-> (forall x. Rep PasswordState x -> PasswordState)
-> Generic PasswordState
forall x. Rep PasswordState x -> PasswordState
forall x. PasswordState -> Rep PasswordState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PasswordState x -> PasswordState
$cfrom :: forall x. PasswordState -> Rep PasswordState x
Generic)
data RecoveryEmailAddress
  = -- | Contains information about the current recovery email address 
  RecoveryEmailAddress
    { -- | Recovery email address
      RecoveryEmailAddress -> T
recovery_email_address_1 :: T
    }
  deriving (I32 -> RecoveryEmailAddress -> ShowS
[RecoveryEmailAddress] -> ShowS
RecoveryEmailAddress -> String
(I32 -> RecoveryEmailAddress -> ShowS)
-> (RecoveryEmailAddress -> String)
-> ([RecoveryEmailAddress] -> ShowS)
-> Show RecoveryEmailAddress
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoveryEmailAddress] -> ShowS
$cshowList :: [RecoveryEmailAddress] -> ShowS
show :: RecoveryEmailAddress -> String
$cshow :: RecoveryEmailAddress -> String
showsPrec :: I32 -> RecoveryEmailAddress -> ShowS
$cshowsPrec :: I32 -> RecoveryEmailAddress -> ShowS
Show, RecoveryEmailAddress -> RecoveryEmailAddress -> Bool
(RecoveryEmailAddress -> RecoveryEmailAddress -> Bool)
-> (RecoveryEmailAddress -> RecoveryEmailAddress -> Bool)
-> Eq RecoveryEmailAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoveryEmailAddress -> RecoveryEmailAddress -> Bool
$c/= :: RecoveryEmailAddress -> RecoveryEmailAddress -> Bool
== :: RecoveryEmailAddress -> RecoveryEmailAddress -> Bool
$c== :: RecoveryEmailAddress -> RecoveryEmailAddress -> Bool
Eq, (forall x. RecoveryEmailAddress -> Rep RecoveryEmailAddress x)
-> (forall x. Rep RecoveryEmailAddress x -> RecoveryEmailAddress)
-> Generic RecoveryEmailAddress
forall x. Rep RecoveryEmailAddress x -> RecoveryEmailAddress
forall x. RecoveryEmailAddress -> Rep RecoveryEmailAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoveryEmailAddress x -> RecoveryEmailAddress
$cfrom :: forall x. RecoveryEmailAddress -> Rep RecoveryEmailAddress x
Generic)
data TemporaryPasswordState
  = -- | Returns information about the availability of a temporary password, which can be used for payments 
  TemporaryPasswordState
    { -- | True, if a temporary password is available 
      TemporaryPasswordState -> Bool
has_password_1 :: Bool,
      -- | Time left before the temporary password expires, in seconds
      TemporaryPasswordState -> I32
valid_for_1 :: I32
    }
  deriving (I32 -> TemporaryPasswordState -> ShowS
[TemporaryPasswordState] -> ShowS
TemporaryPasswordState -> String
(I32 -> TemporaryPasswordState -> ShowS)
-> (TemporaryPasswordState -> String)
-> ([TemporaryPasswordState] -> ShowS)
-> Show TemporaryPasswordState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TemporaryPasswordState] -> ShowS
$cshowList :: [TemporaryPasswordState] -> ShowS
show :: TemporaryPasswordState -> String
$cshow :: TemporaryPasswordState -> String
showsPrec :: I32 -> TemporaryPasswordState -> ShowS
$cshowsPrec :: I32 -> TemporaryPasswordState -> ShowS
Show, TemporaryPasswordState -> TemporaryPasswordState -> Bool
(TemporaryPasswordState -> TemporaryPasswordState -> Bool)
-> (TemporaryPasswordState -> TemporaryPasswordState -> Bool)
-> Eq TemporaryPasswordState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TemporaryPasswordState -> TemporaryPasswordState -> Bool
$c/= :: TemporaryPasswordState -> TemporaryPasswordState -> Bool
== :: TemporaryPasswordState -> TemporaryPasswordState -> Bool
$c== :: TemporaryPasswordState -> TemporaryPasswordState -> Bool
Eq, (forall x. TemporaryPasswordState -> Rep TemporaryPasswordState x)
-> (forall x.
    Rep TemporaryPasswordState x -> TemporaryPasswordState)
-> Generic TemporaryPasswordState
forall x. Rep TemporaryPasswordState x -> TemporaryPasswordState
forall x. TemporaryPasswordState -> Rep TemporaryPasswordState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TemporaryPasswordState x -> TemporaryPasswordState
$cfrom :: forall x. TemporaryPasswordState -> Rep TemporaryPasswordState x
Generic)
data LocalFile
  = -- | Represents a local file
  LocalFile
    { -- | Local path to the locally available file part; may be empty
      LocalFile -> T
path_1 :: T,
      -- | True, if it is possible to try to download or generate the file
      LocalFile -> Bool
can_be_downloaded_1 :: Bool,
      -- | True, if the file can be deleted
      LocalFile -> Bool
can_be_deleted_1 :: Bool,
      -- | True, if the file is currently being downloaded (or a local copy is being generated by some other means)
      LocalFile -> Bool
is_downloading_active_1 :: Bool,
      -- | True, if the local copy is fully available
      LocalFile -> Bool
is_downloading_completed_1 :: Bool,
      -- | Download will be started from this offset. downloaded_prefix_size is calculated from this offset
      LocalFile -> I32
download_offset_1 :: I32,
      -- | If is_downloading_completed is false, then only some prefix of the file starting from download_offset is ready to be read. downloaded_prefix_size is the size of that prefix
      LocalFile -> I32
downloaded_prefix_size_1 :: I32,
      -- | Total downloaded file bytes. Should be used only for calculating download progress. The actual file size may be bigger, and some parts of it may contain garbage
      LocalFile -> I32
downloaded_size_1 :: I32
    }
  deriving (I32 -> LocalFile -> ShowS
[LocalFile] -> ShowS
LocalFile -> String
(I32 -> LocalFile -> ShowS)
-> (LocalFile -> String)
-> ([LocalFile] -> ShowS)
-> Show LocalFile
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LocalFile] -> ShowS
$cshowList :: [LocalFile] -> ShowS
show :: LocalFile -> String
$cshow :: LocalFile -> String
showsPrec :: I32 -> LocalFile -> ShowS
$cshowsPrec :: I32 -> LocalFile -> ShowS
Show, LocalFile -> LocalFile -> Bool
(LocalFile -> LocalFile -> Bool)
-> (LocalFile -> LocalFile -> Bool) -> Eq LocalFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalFile -> LocalFile -> Bool
$c/= :: LocalFile -> LocalFile -> Bool
== :: LocalFile -> LocalFile -> Bool
$c== :: LocalFile -> LocalFile -> Bool
Eq, (forall x. LocalFile -> Rep LocalFile x)
-> (forall x. Rep LocalFile x -> LocalFile) -> Generic LocalFile
forall x. Rep LocalFile x -> LocalFile
forall x. LocalFile -> Rep LocalFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LocalFile x -> LocalFile
$cfrom :: forall x. LocalFile -> Rep LocalFile x
Generic)
data RemoteFile
  = -- | Represents a remote file
  RemoteFile
    { -- | Remote file identifier; may be empty. Can be used by the current user across application restarts or even from other devices. Uniquely identifies a file, but a file can have a lot of different valid identifiers.
      RemoteFile -> T
id_1 :: T,
      -- | Unique file identifier; may be empty if unknown. The unique file identifier which is the same for the same file even for different users and is persistent over time
      RemoteFile -> T
unique_id_1 :: T,
      -- | True, if the file is currently being uploaded (or a remote copy is being generated by some other means)
      RemoteFile -> Bool
is_uploading_active_1 :: Bool,
      -- | True, if a remote copy is fully available
      RemoteFile -> Bool
is_uploading_completed_1 :: Bool,
      -- | Size of the remote available part of the file; 0 if unknown
      RemoteFile -> I32
uploaded_size_1 :: I32
    }
  deriving (I32 -> RemoteFile -> ShowS
[RemoteFile] -> ShowS
RemoteFile -> String
(I32 -> RemoteFile -> ShowS)
-> (RemoteFile -> String)
-> ([RemoteFile] -> ShowS)
-> Show RemoteFile
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoteFile] -> ShowS
$cshowList :: [RemoteFile] -> ShowS
show :: RemoteFile -> String
$cshow :: RemoteFile -> String
showsPrec :: I32 -> RemoteFile -> ShowS
$cshowsPrec :: I32 -> RemoteFile -> ShowS
Show, RemoteFile -> RemoteFile -> Bool
(RemoteFile -> RemoteFile -> Bool)
-> (RemoteFile -> RemoteFile -> Bool) -> Eq RemoteFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoteFile -> RemoteFile -> Bool
$c/= :: RemoteFile -> RemoteFile -> Bool
== :: RemoteFile -> RemoteFile -> Bool
$c== :: RemoteFile -> RemoteFile -> Bool
Eq, (forall x. RemoteFile -> Rep RemoteFile x)
-> (forall x. Rep RemoteFile x -> RemoteFile) -> Generic RemoteFile
forall x. Rep RemoteFile x -> RemoteFile
forall x. RemoteFile -> Rep RemoteFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoteFile x -> RemoteFile
$cfrom :: forall x. RemoteFile -> Rep RemoteFile x
Generic)
data File
  = -- | Represents a file
  File
    { -- | Unique file identifier
      File -> I32
id_1 :: I32,
      -- | File size; 0 if unknown
      File -> I32
size_1 :: I32,
      -- | Expected file size in case the exact file size is unknown, but an approximate size is known. Can be used to show download/upload progress
      File -> I32
expected_size_1 :: I32,
      -- | Information about the local copy of the file
      File -> LocalFile
local_1 :: LocalFile,
      -- | Information about the remote copy of the file
      File -> RemoteFile
remote_1 :: RemoteFile
    }
  deriving (I32 -> File -> ShowS
[File] -> ShowS
File -> String
(I32 -> File -> ShowS)
-> (File -> String) -> ([File] -> ShowS) -> Show File
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [File] -> ShowS
$cshowList :: [File] -> ShowS
show :: File -> String
$cshow :: File -> String
showsPrec :: I32 -> File -> ShowS
$cshowsPrec :: I32 -> File -> ShowS
Show, File -> File -> Bool
(File -> File -> Bool) -> (File -> File -> Bool) -> Eq File
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: File -> File -> Bool
$c/= :: File -> File -> Bool
== :: File -> File -> Bool
$c== :: File -> File -> Bool
Eq, (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)
-- | Points to a file
data InputFile
  = -- | A file defined by its unique ID 
  InputFileId
    { -- | Unique file identifier
      InputFile -> I32
id_1 :: I32
    }
  | -- | A file defined by its remote ID. The remote ID is guaranteed to be usable only if the corresponding file is still accessible to the user and known to TDLib.
  InputFileRemote
    { -- | Remote file identifier
      InputFile -> T
id_2 :: T
    }
  | -- | A file defined by a local path 
  InputFileLocal
    { -- | Local path to the file
      InputFile -> T
path_3 :: T
    }
  | -- | A file generated by the client 
  InputFileGenerated
    { -- | Local path to a file from which the file is generated; may be empty if there is no such file
      InputFile -> T
original_path_4 :: T,
      -- | String specifying the conversion applied to the original file; should be persistent across application restarts. Conversions beginning with '#' are reserved for internal TDLib usage
      InputFile -> T
conversion_4 :: T,
      -- | Expected size of the generated file; 0 if unknown
      InputFile -> I32
expected_size_4 :: I32
    }
  deriving (I32 -> InputFile -> ShowS
[InputFile] -> ShowS
InputFile -> String
(I32 -> InputFile -> ShowS)
-> (InputFile -> String)
-> ([InputFile] -> ShowS)
-> Show InputFile
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputFile] -> ShowS
$cshowList :: [InputFile] -> ShowS
show :: InputFile -> String
$cshow :: InputFile -> String
showsPrec :: I32 -> InputFile -> ShowS
$cshowsPrec :: I32 -> InputFile -> ShowS
Show, InputFile -> InputFile -> Bool
(InputFile -> InputFile -> Bool)
-> (InputFile -> InputFile -> Bool) -> Eq InputFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputFile -> InputFile -> Bool
$c/= :: InputFile -> InputFile -> Bool
== :: InputFile -> InputFile -> Bool
$c== :: InputFile -> InputFile -> Bool
Eq, (forall x. InputFile -> Rep InputFile x)
-> (forall x. Rep InputFile x -> InputFile) -> Generic InputFile
forall x. Rep InputFile x -> InputFile
forall x. InputFile -> Rep InputFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputFile x -> InputFile
$cfrom :: forall x. InputFile -> Rep InputFile x
Generic)
data PhotoSize
  = -- | Photo description 
  PhotoSize
    { -- | Thumbnail type (see https://core.telegram.org/constructor/photoSize) 
      PhotoSize -> T
type_1 :: T,
      -- | Information about the photo file 
      PhotoSize -> File
photo_1 :: File,
      -- | Photo width 
      PhotoSize -> I32
width_1 :: I32,
      -- | Photo height
      PhotoSize -> I32
height_1 :: I32
    }
  deriving (I32 -> PhotoSize -> ShowS
[PhotoSize] -> ShowS
PhotoSize -> String
(I32 -> PhotoSize -> ShowS)
-> (PhotoSize -> String)
-> ([PhotoSize] -> ShowS)
-> Show PhotoSize
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PhotoSize] -> ShowS
$cshowList :: [PhotoSize] -> ShowS
show :: PhotoSize -> String
$cshow :: PhotoSize -> String
showsPrec :: I32 -> PhotoSize -> ShowS
$cshowsPrec :: I32 -> PhotoSize -> ShowS
Show, PhotoSize -> PhotoSize -> Bool
(PhotoSize -> PhotoSize -> Bool)
-> (PhotoSize -> PhotoSize -> Bool) -> Eq PhotoSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhotoSize -> PhotoSize -> Bool
$c/= :: PhotoSize -> PhotoSize -> Bool
== :: PhotoSize -> PhotoSize -> Bool
$c== :: PhotoSize -> PhotoSize -> Bool
Eq, (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)
data Minithumbnail
  = -- | Thumbnail image of a very poor quality and low resolution 
  Minithumbnail
    { -- | Thumbnail width, usually doesn't exceed 40 
      Minithumbnail -> I32
width_1 :: I32,
      -- | Thumbnail height, usually doesn't exceed 40 
      Minithumbnail -> I32
height_1 :: I32,
      -- | The thumbnail in JPEG format
      Minithumbnail -> ByteString64
data_1 :: ByteString64
    }
  deriving (I32 -> Minithumbnail -> ShowS
[Minithumbnail] -> ShowS
Minithumbnail -> String
(I32 -> Minithumbnail -> ShowS)
-> (Minithumbnail -> String)
-> ([Minithumbnail] -> ShowS)
-> Show Minithumbnail
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Minithumbnail] -> ShowS
$cshowList :: [Minithumbnail] -> ShowS
show :: Minithumbnail -> String
$cshow :: Minithumbnail -> String
showsPrec :: I32 -> Minithumbnail -> ShowS
$cshowsPrec :: I32 -> Minithumbnail -> ShowS
Show, Minithumbnail -> Minithumbnail -> Bool
(Minithumbnail -> Minithumbnail -> Bool)
-> (Minithumbnail -> Minithumbnail -> Bool) -> Eq Minithumbnail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Minithumbnail -> Minithumbnail -> Bool
$c/= :: Minithumbnail -> Minithumbnail -> Bool
== :: Minithumbnail -> Minithumbnail -> Bool
$c== :: Minithumbnail -> Minithumbnail -> Bool
Eq, (forall x. Minithumbnail -> Rep Minithumbnail x)
-> (forall x. Rep Minithumbnail x -> Minithumbnail)
-> Generic Minithumbnail
forall x. Rep Minithumbnail x -> Minithumbnail
forall x. Minithumbnail -> Rep Minithumbnail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Minithumbnail x -> Minithumbnail
$cfrom :: forall x. Minithumbnail -> Rep Minithumbnail x
Generic)
-- | Part of the face, relative to which a mask should be placed
data MaskPoint
  = -- | A mask should be placed relatively to the forehead
  MaskPointForehead
    { 
    }
  | -- | A mask should be placed relatively to the eyes
  MaskPointEyes
    { 
    }
  | -- | A mask should be placed relatively to the mouth
  MaskPointMouth
    { 
    }
  | -- | A mask should be placed relatively to the chin
  MaskPointChin
    { 
    }
  deriving (I32 -> MaskPoint -> ShowS
[MaskPoint] -> ShowS
MaskPoint -> String
(I32 -> MaskPoint -> ShowS)
-> (MaskPoint -> String)
-> ([MaskPoint] -> ShowS)
-> Show MaskPoint
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaskPoint] -> ShowS
$cshowList :: [MaskPoint] -> ShowS
show :: MaskPoint -> String
$cshow :: MaskPoint -> String
showsPrec :: I32 -> MaskPoint -> ShowS
$cshowsPrec :: I32 -> MaskPoint -> ShowS
Show, MaskPoint -> MaskPoint -> Bool
(MaskPoint -> MaskPoint -> Bool)
-> (MaskPoint -> MaskPoint -> Bool) -> Eq MaskPoint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaskPoint -> MaskPoint -> Bool
$c/= :: MaskPoint -> MaskPoint -> Bool
== :: MaskPoint -> MaskPoint -> Bool
$c== :: MaskPoint -> MaskPoint -> Bool
Eq, (forall x. MaskPoint -> Rep MaskPoint x)
-> (forall x. Rep MaskPoint x -> MaskPoint) -> Generic MaskPoint
forall x. Rep MaskPoint x -> MaskPoint
forall x. MaskPoint -> Rep MaskPoint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MaskPoint x -> MaskPoint
$cfrom :: forall x. MaskPoint -> Rep MaskPoint x
Generic)
data MaskPosition
  = -- | Position on a photo where a mask should be placed 
  MaskPosition
    { -- | Part of the face, relative to which the mask should be placed
      MaskPosition -> MaskPoint
point_1 :: MaskPoint,
      -- | Shift by X-axis measured in widths of the mask scaled to the face size, from left to right. (For example, -1.0 will place the mask just to the left of the default mask position)
      MaskPosition -> Double
x_shift_1 :: Double,
      -- | Shift by Y-axis measured in heights of the mask scaled to the face size, from top to bottom. (For example, 1.0 will place the mask just below the default mask position)
      MaskPosition -> Double
y_shift_1 :: Double,
      -- | Mask scaling coefficient. (For example, 2.0 means a doubled size)
      MaskPosition -> Double
scale_1 :: Double
    }
  deriving (I32 -> MaskPosition -> ShowS
[MaskPosition] -> ShowS
MaskPosition -> String
(I32 -> MaskPosition -> ShowS)
-> (MaskPosition -> String)
-> ([MaskPosition] -> ShowS)
-> Show MaskPosition
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MaskPosition] -> ShowS
$cshowList :: [MaskPosition] -> ShowS
show :: MaskPosition -> String
$cshow :: MaskPosition -> String
showsPrec :: I32 -> MaskPosition -> ShowS
$cshowsPrec :: I32 -> MaskPosition -> ShowS
Show, MaskPosition -> MaskPosition -> Bool
(MaskPosition -> MaskPosition -> Bool)
-> (MaskPosition -> MaskPosition -> Bool) -> Eq MaskPosition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MaskPosition -> MaskPosition -> Bool
$c/= :: MaskPosition -> MaskPosition -> Bool
== :: MaskPosition -> MaskPosition -> Bool
$c== :: MaskPosition -> MaskPosition -> Bool
Eq, (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)
data PollOption
  = -- | Describes one answer option of a poll 
  PollOption
    { -- | Option text, 1-100 characters 
      PollOption -> T
text_1 :: T,
      -- | Number of voters for this option, available only for closed or voted polls 
      PollOption -> I32
voter_count_1 :: I32,
      -- | The percentage of votes for this option, 0-100
      PollOption -> I32
vote_percentage_1 :: I32,
      -- | True, if the option was chosen by the user 
      PollOption -> Bool
is_chosen_1 :: Bool,
      -- | True, if the option is being chosen by a pending setPollAnswer request
      PollOption -> Bool
is_being_chosen_1 :: Bool
    }
  deriving (I32 -> PollOption -> ShowS
[PollOption] -> ShowS
PollOption -> String
(I32 -> PollOption -> ShowS)
-> (PollOption -> String)
-> ([PollOption] -> ShowS)
-> Show PollOption
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollOption] -> ShowS
$cshowList :: [PollOption] -> ShowS
show :: PollOption -> String
$cshow :: PollOption -> String
showsPrec :: I32 -> PollOption -> ShowS
$cshowsPrec :: I32 -> PollOption -> ShowS
Show, PollOption -> PollOption -> Bool
(PollOption -> PollOption -> Bool)
-> (PollOption -> PollOption -> Bool) -> Eq PollOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollOption -> PollOption -> Bool
$c/= :: PollOption -> PollOption -> Bool
== :: PollOption -> PollOption -> Bool
$c== :: PollOption -> PollOption -> Bool
Eq, (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)
-- | Describes the type of a poll
data PollType
  = -- | A regular poll 
  PollTypeRegular
    { -- | True, if multiple answer options can be chosen simultaneously
      PollType -> Bool
allow_multiple_answers_1 :: Bool
    }
  | -- | A poll in quiz mode, which has exactly one correct answer option and can be answered only once
  PollTypeQuiz
    { -- | 0-based identifier of the correct answer option; -1 for a yet unanswered poll
      PollType -> I32
correct_option_id_2 :: I32,
      -- | Text that is shown when the user chooses an incorrect answer or taps on the lamp icon, 0-200 characters with at most 2 line feeds; empty for a yet unanswered poll
      PollType -> FormattedText
explanation_2 :: FormattedText
    }
  deriving (I32 -> PollType -> ShowS
[PollType] -> ShowS
PollType -> String
(I32 -> PollType -> ShowS)
-> (PollType -> String) -> ([PollType] -> ShowS) -> Show PollType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PollType] -> ShowS
$cshowList :: [PollType] -> ShowS
show :: PollType -> String
$cshow :: PollType -> String
showsPrec :: I32 -> PollType -> ShowS
$cshowsPrec :: I32 -> PollType -> ShowS
Show, PollType -> PollType -> Bool
(PollType -> PollType -> Bool)
-> (PollType -> PollType -> Bool) -> Eq PollType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PollType -> PollType -> Bool
$c/= :: PollType -> PollType -> Bool
== :: PollType -> PollType -> Bool
$c== :: PollType -> PollType -> Bool
Eq, (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)
data Animation
  = -- | Describes an animation file. The animation must be encoded in GIF or MPEG4 format 
  Animation
    { -- | Duration of the animation, in seconds; as defined by the sender 
      Animation -> I32
duration_1 :: I32,
      -- | Width of the animation 
      Animation -> I32
width_1 :: I32,
      -- | Height of the animation
      Animation -> I32
height_1 :: I32,
      -- | Original name of the file; as defined by the sender 
      Animation -> T
file_name_1 :: T,
      -- | MIME type of the file, usually "image/gif" or "video/mp4"
      Animation -> T
mime_type_1 :: T,
      -- | Animation minithumbnail; may be null 
      Animation -> Minithumbnail
minithumbnail_1 :: Minithumbnail,
      -- | Animation thumbnail; may be null 
      Animation -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | File containing the animation
      Animation -> File
animation_1 :: File
    }
  deriving (I32 -> Animation -> ShowS
[Animation] -> ShowS
Animation -> String
(I32 -> Animation -> ShowS)
-> (Animation -> String)
-> ([Animation] -> ShowS)
-> Show Animation
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Animation] -> ShowS
$cshowList :: [Animation] -> ShowS
show :: Animation -> String
$cshow :: Animation -> String
showsPrec :: I32 -> Animation -> ShowS
$cshowsPrec :: I32 -> Animation -> ShowS
Show, Animation -> Animation -> Bool
(Animation -> Animation -> Bool)
-> (Animation -> Animation -> Bool) -> Eq Animation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Animation -> Animation -> Bool
$c/= :: Animation -> Animation -> Bool
== :: Animation -> Animation -> Bool
$c== :: Animation -> Animation -> Bool
Eq, (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)
data Audio
  = -- | Describes an audio file. Audio is usually in MP3 or M4A format 
  Audio
    { -- | Duration of the audio, in seconds; as defined by the sender 
      Audio -> I32
duration_1 :: I32,
      -- | Title of the audio; as defined by the sender 
      Audio -> T
title_1 :: T,
      -- | Performer of the audio; as defined by the sender
      Audio -> T
performer_1 :: T,
      -- | Original name of the file; as defined by the sender 
      Audio -> T
file_name_1 :: T,
      -- | The MIME type of the file; as defined by the sender 
      Audio -> T
mime_type_1 :: T,
      -- | The minithumbnail of the album cover; may be null 
      Audio -> Minithumbnail
album_cover_minithumbnail_1 :: Minithumbnail,
      -- | The thumbnail of the album cover; as defined by the sender. The full size thumbnail should be extracted from the downloaded file; may be null 
      Audio -> PhotoSize
album_cover_thumbnail_1 :: PhotoSize,
      -- | File containing the audio
      Audio -> File
audio_1 :: File
    }
  deriving (I32 -> Audio -> ShowS
[Audio] -> ShowS
Audio -> String
(I32 -> Audio -> ShowS)
-> (Audio -> String) -> ([Audio] -> ShowS) -> Show Audio
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Audio] -> ShowS
$cshowList :: [Audio] -> ShowS
show :: Audio -> String
$cshow :: Audio -> String
showsPrec :: I32 -> Audio -> ShowS
$cshowsPrec :: I32 -> Audio -> ShowS
Show, Audio -> Audio -> Bool
(Audio -> Audio -> Bool) -> (Audio -> Audio -> Bool) -> Eq Audio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Audio -> Audio -> Bool
$c/= :: Audio -> Audio -> Bool
== :: Audio -> Audio -> Bool
$c== :: Audio -> Audio -> Bool
Eq, (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)
data Document
  = -- | Describes a document of any type 
  Document
    { -- | Original name of the file; as defined by the sender 
      Document -> T
file_name_1 :: T,
      -- | MIME type of the file; as defined by the sender
      Document -> T
mime_type_1 :: T,
      -- | Document minithumbnail; may be null 
      Document -> Minithumbnail
minithumbnail_1 :: Minithumbnail,
      -- | Document thumbnail in JPEG or PNG format (PNG will be used only for background patterns); as defined by the sender; may be null 
      Document -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | File containing the document
      Document -> File
document_1 :: File
    }
  deriving (I32 -> Document -> ShowS
[Document] -> ShowS
Document -> String
(I32 -> Document -> ShowS)
-> (Document -> String) -> ([Document] -> ShowS) -> Show Document
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Document] -> ShowS
$cshowList :: [Document] -> ShowS
show :: Document -> String
$cshow :: Document -> String
showsPrec :: I32 -> Document -> ShowS
$cshowsPrec :: I32 -> Document -> ShowS
Show, Document -> Document -> Bool
(Document -> Document -> Bool)
-> (Document -> Document -> Bool) -> Eq Document
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c== :: Document -> Document -> Bool
Eq, (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)
data Photo
  = -- | Describes a photo 
  Photo
    { -- | True, if stickers were added to the photo 
      Photo -> Bool
has_stickers_1 :: Bool,
      -- | Photo minithumbnail; may be null 
      Photo -> Minithumbnail
minithumbnail_1 :: Minithumbnail,
      -- | Available variants of the photo, in different sizes
      Photo -> [PhotoSize]
sizes_1 :: ([]) (PhotoSize)
    }
  deriving (I32 -> Photo -> ShowS
[Photo] -> ShowS
Photo -> String
(I32 -> Photo -> ShowS)
-> (Photo -> String) -> ([Photo] -> ShowS) -> Show Photo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Photo] -> ShowS
$cshowList :: [Photo] -> ShowS
show :: Photo -> String
$cshow :: Photo -> String
showsPrec :: I32 -> Photo -> ShowS
$cshowsPrec :: I32 -> Photo -> ShowS
Show, Photo -> Photo -> Bool
(Photo -> Photo -> Bool) -> (Photo -> Photo -> Bool) -> Eq Photo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Photo -> Photo -> Bool
$c/= :: Photo -> Photo -> Bool
== :: Photo -> Photo -> Bool
$c== :: Photo -> Photo -> Bool
Eq, (forall x. Photo -> Rep Photo x)
-> (forall x. Rep Photo x -> Photo) -> Generic Photo
forall x. Rep Photo x -> Photo
forall x. Photo -> Rep Photo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Photo x -> Photo
$cfrom :: forall x. Photo -> Rep Photo x
Generic)
data Sticker
  = -- | Describes a sticker 
  Sticker
    { -- | The identifier of the sticker set to which the sticker belongs; 0 if none 
      Sticker -> I64
set_id_1 :: I64,
      -- | Sticker width; as defined by the sender 
      Sticker -> I32
width_1 :: I32,
      -- | Sticker height; as defined by the sender
      Sticker -> I32
height_1 :: I32,
      -- | Emoji corresponding to the sticker 
      Sticker -> T
emoji_1 :: T,
      -- | True, if the sticker is an animated sticker in TGS format 
      Sticker -> Bool
is_animated_1 :: Bool,
      -- | True, if the sticker is a mask 
      Sticker -> Bool
is_mask_1 :: Bool,
      -- | Position where the mask should be placed; may be null 
      Sticker -> MaskPosition
mask_position_1 :: MaskPosition,
      -- | Sticker thumbnail in WEBP or JPEG format; may be null 
      Sticker -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | File containing the sticker
      Sticker -> File
sticker_1 :: File
    }
  deriving (I32 -> Sticker -> ShowS
[Sticker] -> ShowS
Sticker -> String
(I32 -> Sticker -> ShowS)
-> (Sticker -> String) -> ([Sticker] -> ShowS) -> Show Sticker
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Sticker] -> ShowS
$cshowList :: [Sticker] -> ShowS
show :: Sticker -> String
$cshow :: Sticker -> String
showsPrec :: I32 -> Sticker -> ShowS
$cshowsPrec :: I32 -> Sticker -> ShowS
Show, Sticker -> Sticker -> Bool
(Sticker -> Sticker -> Bool)
-> (Sticker -> Sticker -> Bool) -> Eq Sticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sticker -> Sticker -> Bool
$c/= :: Sticker -> Sticker -> Bool
== :: Sticker -> Sticker -> Bool
$c== :: Sticker -> Sticker -> Bool
Eq, (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)
data Video
  = -- | Describes a video file 
  Video
    { -- | Duration of the video, in seconds; as defined by the sender 
      Video -> I32
duration_1 :: I32,
      -- | Video width; as defined by the sender 
      Video -> I32
width_1 :: I32,
      -- | Video height; as defined by the sender
      Video -> I32
height_1 :: I32,
      -- | Original name of the file; as defined by the sender 
      Video -> T
file_name_1 :: T,
      -- | MIME type of the file; as defined by the sender 
      Video -> T
mime_type_1 :: T,
      -- | True, if stickers were added to the video
      Video -> Bool
has_stickers_1 :: Bool,
      -- | True, if the video should be tried to be streamed 
      Video -> Bool
supports_streaming_1 :: Bool,
      -- | Video minithumbnail; may be null 
      Video -> Minithumbnail
minithumbnail_1 :: Minithumbnail,
      -- | Video thumbnail; as defined by the sender; may be null 
      Video -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | File containing the video
      Video -> File
video_1 :: File
    }
  deriving (I32 -> Video -> ShowS
[Video] -> ShowS
Video -> String
(I32 -> Video -> ShowS)
-> (Video -> String) -> ([Video] -> ShowS) -> Show Video
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Video] -> ShowS
$cshowList :: [Video] -> ShowS
show :: Video -> String
$cshow :: Video -> String
showsPrec :: I32 -> Video -> ShowS
$cshowsPrec :: I32 -> Video -> ShowS
Show, Video -> Video -> Bool
(Video -> Video -> Bool) -> (Video -> Video -> Bool) -> Eq Video
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Video -> Video -> Bool
$c/= :: Video -> Video -> Bool
== :: Video -> Video -> Bool
$c== :: Video -> Video -> Bool
Eq, (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)
data VideoNote
  = -- | Describes a video note. The video must be equal in width and height, cropped to a circle, and stored in MPEG4 format 
  VideoNote
    { -- | Duration of the video, in seconds; as defined by the sender 
      VideoNote -> I32
duration_1 :: I32,
      -- | Video width and height; as defined by the sender 
      VideoNote -> I32
length_1 :: I32,
      -- | Video minithumbnail; may be null 
      VideoNote -> Minithumbnail
minithumbnail_1 :: Minithumbnail,
      -- | Video thumbnail; as defined by the sender; may be null 
      VideoNote -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | File containing the video
      VideoNote -> File
video_1 :: File
    }
  deriving (I32 -> VideoNote -> ShowS
[VideoNote] -> ShowS
VideoNote -> String
(I32 -> VideoNote -> ShowS)
-> (VideoNote -> String)
-> ([VideoNote] -> ShowS)
-> Show VideoNote
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VideoNote] -> ShowS
$cshowList :: [VideoNote] -> ShowS
show :: VideoNote -> String
$cshow :: VideoNote -> String
showsPrec :: I32 -> VideoNote -> ShowS
$cshowsPrec :: I32 -> VideoNote -> ShowS
Show, VideoNote -> VideoNote -> Bool
(VideoNote -> VideoNote -> Bool)
-> (VideoNote -> VideoNote -> Bool) -> Eq VideoNote
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VideoNote -> VideoNote -> Bool
$c/= :: VideoNote -> VideoNote -> Bool
== :: VideoNote -> VideoNote -> Bool
$c== :: VideoNote -> VideoNote -> Bool
Eq, (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)
data VoiceNote
  = -- | Describes a voice note. The voice note must be encoded with the Opus codec, and stored inside an OGG container. Voice notes can have only a single audio channel 
  VoiceNote
    { -- | Duration of the voice note, in seconds; as defined by the sender
      VoiceNote -> I32
duration_1 :: I32,
      -- | A waveform representation of the voice note in 5-bit format 
      VoiceNote -> ByteString64
waveform_1 :: ByteString64,
      -- | MIME type of the file; as defined by the sender 
      VoiceNote -> T
mime_type_1 :: T,
      -- | File containing the voice note
      VoiceNote -> File
voice_1 :: File
    }
  deriving (I32 -> VoiceNote -> ShowS
[VoiceNote] -> ShowS
VoiceNote -> String
(I32 -> VoiceNote -> ShowS)
-> (VoiceNote -> String)
-> ([VoiceNote] -> ShowS)
-> Show VoiceNote
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [VoiceNote] -> ShowS
$cshowList :: [VoiceNote] -> ShowS
show :: VoiceNote -> String
$cshow :: VoiceNote -> String
showsPrec :: I32 -> VoiceNote -> ShowS
$cshowsPrec :: I32 -> VoiceNote -> ShowS
Show, VoiceNote -> VoiceNote -> Bool
(VoiceNote -> VoiceNote -> Bool)
-> (VoiceNote -> VoiceNote -> Bool) -> Eq VoiceNote
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VoiceNote -> VoiceNote -> Bool
$c/= :: VoiceNote -> VoiceNote -> Bool
== :: VoiceNote -> VoiceNote -> Bool
$c== :: VoiceNote -> VoiceNote -> Bool
Eq, (forall x. VoiceNote -> Rep VoiceNote x)
-> (forall x. Rep VoiceNote x -> VoiceNote) -> Generic VoiceNote
forall x. Rep VoiceNote x -> VoiceNote
forall x. VoiceNote -> Rep VoiceNote x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep VoiceNote x -> VoiceNote
$cfrom :: forall x. VoiceNote -> Rep VoiceNote x
Generic)
data Contact
  = -- | Describes a user contact 
  Contact
    { -- | Phone number of the user 
      Contact -> T
phone_number_1 :: T,
      -- | First name of the user; 1-255 characters in length 
      Contact -> T
first_name_1 :: T,
      -- | Last name of the user 
      Contact -> T
last_name_1 :: T,
      -- | Additional data about the user in a form of vCard; 0-2048 bytes in length 
      Contact -> T
vcard_1 :: T,
      -- | Identifier of the user, if known; otherwise 0
      Contact -> I32
user_id_1 :: I32
    }
  deriving (I32 -> Contact -> ShowS
[Contact] -> ShowS
Contact -> String
(I32 -> Contact -> ShowS)
-> (Contact -> String) -> ([Contact] -> ShowS) -> Show Contact
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Contact] -> ShowS
$cshowList :: [Contact] -> ShowS
show :: Contact -> String
$cshow :: Contact -> String
showsPrec :: I32 -> Contact -> ShowS
$cshowsPrec :: I32 -> Contact -> ShowS
Show, Contact -> Contact -> Bool
(Contact -> Contact -> Bool)
-> (Contact -> Contact -> Bool) -> Eq Contact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Contact -> Contact -> Bool
$c/= :: Contact -> Contact -> Bool
== :: Contact -> Contact -> Bool
$c== :: Contact -> Contact -> Bool
Eq, (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)
data Location
  = -- | Describes a location on planet Earth 
  Location
    { -- | Latitude of the location in degrees; as defined by the sender 
      Location -> Double
latitude_1 :: Double,
      -- | Longitude of the location, in degrees; as defined by the sender
      Location -> Double
longitude_1 :: Double
    }
  deriving (I32 -> Location -> ShowS
[Location] -> ShowS
Location -> String
(I32 -> Location -> ShowS)
-> (Location -> String) -> ([Location] -> ShowS) -> Show Location
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Location] -> ShowS
$cshowList :: [Location] -> ShowS
show :: Location -> String
$cshow :: Location -> String
showsPrec :: I32 -> Location -> ShowS
$cshowsPrec :: I32 -> Location -> ShowS
Show, Location -> Location -> Bool
(Location -> Location -> Bool)
-> (Location -> Location -> Bool) -> Eq Location
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Location -> Location -> Bool
$c/= :: Location -> Location -> Bool
== :: Location -> Location -> Bool
$c== :: Location -> Location -> Bool
Eq, (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)
data Venue
  = -- | Describes a venue 
  Venue
    { -- | Venue location; as defined by the sender 
      Venue -> Location
location_1 :: Location,
      -- | Venue name; as defined by the sender 
      Venue -> T
title_1 :: T,
      -- | Venue address; as defined by the sender 
      Venue -> T
address_1 :: T,
      -- | Provider of the venue database; as defined by the sender. Currently only "foursquare" needs to be supported
      Venue -> T
provider_1 :: T,
      -- | Identifier of the venue in the provider database; as defined by the sender 
      Venue -> T
id_1 :: T,
      -- | Type of the venue in the provider database; as defined by the sender
      Venue -> T
type_1 :: T
    }
  deriving (I32 -> Venue -> ShowS
[Venue] -> ShowS
Venue -> String
(I32 -> Venue -> ShowS)
-> (Venue -> String) -> ([Venue] -> ShowS) -> Show Venue
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Venue] -> ShowS
$cshowList :: [Venue] -> ShowS
show :: Venue -> String
$cshow :: Venue -> String
showsPrec :: I32 -> Venue -> ShowS
$cshowsPrec :: I32 -> Venue -> ShowS
Show, Venue -> Venue -> Bool
(Venue -> Venue -> Bool) -> (Venue -> Venue -> Bool) -> Eq Venue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Venue -> Venue -> Bool
$c/= :: Venue -> Venue -> Bool
== :: Venue -> Venue -> Bool
$c== :: Venue -> Venue -> Bool
Eq, (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)
data Game
  = -- | Describes a game 
  Game
    { -- | Game ID 
      Game -> I64
id_1 :: I64,
      -- | Game short name. To share a game use the URL https://t.me/{bot_username}?game={game_short_name} 
      Game -> T
short_name_1 :: T,
      -- | Game title 
      Game -> T
title_1 :: T,
      -- | Game text, usually containing scoreboards for a game
      Game -> FormattedText
text_1 :: FormattedText,
      -- | Describes a game 
      Game -> T
description_1 :: T,
      -- | Game photo 
      Game -> Photo
photo_1 :: Photo,
      -- | Game animation; may be null
      Game -> Animation
animation_1 :: Animation
    }
  deriving (I32 -> Game -> ShowS
[Game] -> ShowS
Game -> String
(I32 -> Game -> ShowS)
-> (Game -> String) -> ([Game] -> ShowS) -> Show Game
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Game] -> ShowS
$cshowList :: [Game] -> ShowS
show :: Game -> String
$cshow :: Game -> String
showsPrec :: I32 -> Game -> ShowS
$cshowsPrec :: I32 -> Game -> ShowS
Show, Game -> Game -> Bool
(Game -> Game -> Bool) -> (Game -> Game -> Bool) -> Eq Game
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Game -> Game -> Bool
$c/= :: Game -> Game -> Bool
== :: Game -> Game -> Bool
$c== :: Game -> Game -> Bool
Eq, (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)
data Poll
  = -- | Describes a poll 
  Poll
    { -- | Unique poll identifier 
      Poll -> I64
id_1 :: I64,
      -- | Poll question, 1-255 characters 
      Poll -> T
question_1 :: T,
      -- | List of poll answer options
      Poll -> [PollOption]
options_1 :: ([]) (PollOption),
      -- | Total number of voters, participating in the poll 
      Poll -> I32
total_voter_count_1 :: I32,
      -- | User identifiers of recent voters, if the poll is non-anonymous
      Poll -> [I32]
recent_voter_user_ids_1 :: ([]) (I32),
      -- | True, if the poll is anonymous 
      Poll -> Bool
is_anonymous_1 :: Bool,
      -- | Type of the poll
      Poll -> PollType
type_1 :: PollType,
      -- | Amount of time the poll will be active after creation, in seconds 
      Poll -> I32
open_period_1 :: I32,
      -- | Point in time (Unix timestamp) when the poll will be automatically closed 
      Poll -> I32
close_date_1 :: I32,
      -- | True, if the poll is closed
      Poll -> Bool
is_closed_1 :: Bool
    }
  deriving (I32 -> Poll -> ShowS
[Poll] -> ShowS
Poll -> String
(I32 -> Poll -> ShowS)
-> (Poll -> String) -> ([Poll] -> ShowS) -> Show Poll
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Poll] -> ShowS
$cshowList :: [Poll] -> ShowS
show :: Poll -> String
$cshow :: Poll -> String
showsPrec :: I32 -> Poll -> ShowS
$cshowsPrec :: I32 -> Poll -> ShowS
Show, Poll -> Poll -> Bool
(Poll -> Poll -> Bool) -> (Poll -> Poll -> Bool) -> Eq Poll
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Poll -> Poll -> Bool
$c/= :: Poll -> Poll -> Bool
== :: Poll -> Poll -> Bool
$c== :: Poll -> Poll -> Bool
Eq, (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)
data ProfilePhoto
  = -- | Describes a user profile photo 
  ProfilePhoto
    { -- | Photo identifier; 0 for an empty photo. Can be used to find a photo in a list of userProfilePhotos
      ProfilePhoto -> I64
id_1 :: I64,
      -- | A small (160x160) user profile photo. The file can be downloaded only before the photo is changed 
      ProfilePhoto -> File
small_1 :: File,
      -- | A big (640x640) user profile photo. The file can be downloaded only before the photo is changed
      ProfilePhoto -> File
big_1 :: File
    }
  deriving (I32 -> ProfilePhoto -> ShowS
[ProfilePhoto] -> ShowS
ProfilePhoto -> String
(I32 -> ProfilePhoto -> ShowS)
-> (ProfilePhoto -> String)
-> ([ProfilePhoto] -> ShowS)
-> Show ProfilePhoto
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProfilePhoto] -> ShowS
$cshowList :: [ProfilePhoto] -> ShowS
show :: ProfilePhoto -> String
$cshow :: ProfilePhoto -> String
showsPrec :: I32 -> ProfilePhoto -> ShowS
$cshowsPrec :: I32 -> ProfilePhoto -> ShowS
Show, ProfilePhoto -> ProfilePhoto -> Bool
(ProfilePhoto -> ProfilePhoto -> Bool)
-> (ProfilePhoto -> ProfilePhoto -> Bool) -> Eq ProfilePhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProfilePhoto -> ProfilePhoto -> Bool
$c/= :: ProfilePhoto -> ProfilePhoto -> Bool
== :: ProfilePhoto -> ProfilePhoto -> Bool
$c== :: ProfilePhoto -> ProfilePhoto -> Bool
Eq, (forall x. ProfilePhoto -> Rep ProfilePhoto x)
-> (forall x. Rep ProfilePhoto x -> ProfilePhoto)
-> Generic ProfilePhoto
forall x. Rep ProfilePhoto x -> ProfilePhoto
forall x. ProfilePhoto -> Rep ProfilePhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProfilePhoto x -> ProfilePhoto
$cfrom :: forall x. ProfilePhoto -> Rep ProfilePhoto x
Generic)
data ChatPhoto
  = -- | Describes the photo of a chat 
  ChatPhoto
    { -- | A small (160x160) chat photo. The file can be downloaded only before the photo is changed 
      ChatPhoto -> File
small_1 :: File,
      -- | A big (640x640) chat photo. The file can be downloaded only before the photo is changed
      ChatPhoto -> File
big_1 :: File
    }
  deriving (I32 -> ChatPhoto -> ShowS
[ChatPhoto] -> ShowS
ChatPhoto -> String
(I32 -> ChatPhoto -> ShowS)
-> (ChatPhoto -> String)
-> ([ChatPhoto] -> ShowS)
-> Show ChatPhoto
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatPhoto] -> ShowS
$cshowList :: [ChatPhoto] -> ShowS
show :: ChatPhoto -> String
$cshow :: ChatPhoto -> String
showsPrec :: I32 -> ChatPhoto -> ShowS
$cshowsPrec :: I32 -> ChatPhoto -> ShowS
Show, ChatPhoto -> ChatPhoto -> Bool
(ChatPhoto -> ChatPhoto -> Bool)
-> (ChatPhoto -> ChatPhoto -> Bool) -> Eq ChatPhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatPhoto -> ChatPhoto -> Bool
$c/= :: ChatPhoto -> ChatPhoto -> Bool
== :: ChatPhoto -> ChatPhoto -> Bool
$c== :: ChatPhoto -> ChatPhoto -> Bool
Eq, (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)
-- | Represents the type of a user. The following types are possible: regular users, deleted users and bots
data UserType
  = -- | A regular user
  UserTypeRegular
    { 
    }
  | -- | A deleted user or deleted bot. No information on the user besides the user identifier is available. It is not possible to perform any active actions on this type of user
  UserTypeDeleted
    { 
    }
  | -- | A bot (see https://core.telegram.org/bots) 
  UserTypeBot
    { -- | True, if the bot can be invited to basic group and supergroup chats
      UserType -> Bool
can_join_groups_3 :: Bool,
      -- | True, if the bot can read all messages in basic group or supergroup chats and not just those addressed to the bot. In private and channel chats a bot can always read all messages
      UserType -> Bool
can_read_all_group_messages_3 :: Bool,
      -- | True, if the bot supports inline queries 
      UserType -> Bool
is_inline_3 :: Bool,
      -- | Placeholder for inline queries (displayed on the client input field) 
      UserType -> T
inline_query_placeholder_3 :: T,
      -- | True, if the location of the user should be sent with every inline query to this bot
      UserType -> Bool
need_location_3 :: Bool
    }
  | -- | No information on the user besides the user identifier is available, yet this user has not been deleted. This object is extremely rare and must be handled like a deleted user. It is not possible to perform any actions on users of this type
  UserTypeUnknown
    { 
    }
  deriving (I32 -> UserType -> ShowS
[UserType] -> ShowS
UserType -> String
(I32 -> UserType -> ShowS)
-> (UserType -> String) -> ([UserType] -> ShowS) -> Show UserType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserType] -> ShowS
$cshowList :: [UserType] -> ShowS
show :: UserType -> String
$cshow :: UserType -> String
showsPrec :: I32 -> UserType -> ShowS
$cshowsPrec :: I32 -> UserType -> ShowS
Show, UserType -> UserType -> Bool
(UserType -> UserType -> Bool)
-> (UserType -> UserType -> Bool) -> Eq UserType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserType -> UserType -> Bool
$c/= :: UserType -> UserType -> Bool
== :: UserType -> UserType -> Bool
$c== :: UserType -> UserType -> Bool
Eq, (forall x. UserType -> Rep UserType x)
-> (forall x. Rep UserType x -> UserType) -> Generic UserType
forall x. Rep UserType x -> UserType
forall x. UserType -> Rep UserType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserType x -> UserType
$cfrom :: forall x. UserType -> Rep UserType x
Generic)
data BotCommand
  = -- | Represents a command supported by a bot 
  BotCommand
    { -- | Text of the bot command 
      BotCommand -> T
command_1 :: T,
      -- | Represents a command supported by a bot 
      BotCommand -> T
description_1 :: T
    }
  deriving (I32 -> BotCommand -> ShowS
[BotCommand] -> ShowS
BotCommand -> String
(I32 -> BotCommand -> ShowS)
-> (BotCommand -> String)
-> ([BotCommand] -> ShowS)
-> Show BotCommand
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BotCommand] -> ShowS
$cshowList :: [BotCommand] -> ShowS
show :: BotCommand -> String
$cshow :: BotCommand -> String
showsPrec :: I32 -> BotCommand -> ShowS
$cshowsPrec :: I32 -> BotCommand -> ShowS
Show, BotCommand -> BotCommand -> Bool
(BotCommand -> BotCommand -> Bool)
-> (BotCommand -> BotCommand -> Bool) -> Eq BotCommand
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BotCommand -> BotCommand -> Bool
$c/= :: BotCommand -> BotCommand -> Bool
== :: BotCommand -> BotCommand -> Bool
$c== :: BotCommand -> BotCommand -> Bool
Eq, (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)
data BotInfo
  = -- | Provides information about a bot and its supported commands 
  BotInfo
    { -- | Provides information about a bot and its supported commands 
      BotInfo -> T
description_1 :: T,
      -- | A list of commands supported by the bot
      BotInfo -> [BotCommand]
commands_1 :: ([]) (BotCommand)
    }
  deriving (I32 -> BotInfo -> ShowS
[BotInfo] -> ShowS
BotInfo -> String
(I32 -> BotInfo -> ShowS)
-> (BotInfo -> String) -> ([BotInfo] -> ShowS) -> Show BotInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BotInfo] -> ShowS
$cshowList :: [BotInfo] -> ShowS
show :: BotInfo -> String
$cshow :: BotInfo -> String
showsPrec :: I32 -> BotInfo -> ShowS
$cshowsPrec :: I32 -> BotInfo -> ShowS
Show, BotInfo -> BotInfo -> Bool
(BotInfo -> BotInfo -> Bool)
-> (BotInfo -> BotInfo -> Bool) -> Eq BotInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BotInfo -> BotInfo -> Bool
$c/= :: BotInfo -> BotInfo -> Bool
== :: BotInfo -> BotInfo -> Bool
$c== :: BotInfo -> BotInfo -> Bool
Eq, (forall x. BotInfo -> Rep BotInfo x)
-> (forall x. Rep BotInfo x -> BotInfo) -> Generic BotInfo
forall x. Rep BotInfo x -> BotInfo
forall x. BotInfo -> Rep BotInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BotInfo x -> BotInfo
$cfrom :: forall x. BotInfo -> Rep BotInfo x
Generic)
data ChatLocation
  = -- | Represents a location to which a chat is connected 
  ChatLocation
    { -- | The location 
      ChatLocation -> Location
location_1 :: Location,
      -- | Location address; 1-64 characters, as defined by the chat owner
      ChatLocation -> T
address_1 :: T
    }
  deriving (I32 -> ChatLocation -> ShowS
[ChatLocation] -> ShowS
ChatLocation -> String
(I32 -> ChatLocation -> ShowS)
-> (ChatLocation -> String)
-> ([ChatLocation] -> ShowS)
-> Show ChatLocation
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatLocation] -> ShowS
$cshowList :: [ChatLocation] -> ShowS
show :: ChatLocation -> String
$cshow :: ChatLocation -> String
showsPrec :: I32 -> ChatLocation -> ShowS
$cshowsPrec :: I32 -> ChatLocation -> ShowS
Show, ChatLocation -> ChatLocation -> Bool
(ChatLocation -> ChatLocation -> Bool)
-> (ChatLocation -> ChatLocation -> Bool) -> Eq ChatLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatLocation -> ChatLocation -> Bool
$c/= :: ChatLocation -> ChatLocation -> Bool
== :: ChatLocation -> ChatLocation -> Bool
$c== :: ChatLocation -> ChatLocation -> Bool
Eq, (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)
data User
  = -- | Represents a user 
  User
    { -- | User identifier 
      User -> I32
id_1 :: I32,
      -- | First name of the user 
      User -> T
first_name_1 :: T,
      -- | Last name of the user 
      User -> T
last_name_1 :: T,
      -- | Username of the user
      User -> T
username_1 :: T,
      -- | Phone number of the user 
      User -> T
phone_number_1 :: T,
      -- | Current online status of the user 
      User -> UserStatus
status_1 :: UserStatus,
      -- | Profile photo of the user; may be null
      User -> ProfilePhoto
profile_photo_1 :: ProfilePhoto,
      -- | The user is a contact of the current user
      User -> Bool
is_contact_1 :: Bool,
      -- | The user is a contact of the current user and the current user is a contact of the user
      User -> Bool
is_mutual_contact_1 :: Bool,
      -- | True, if the user is verified 
      User -> Bool
is_verified_1 :: Bool,
      -- | True, if the user is Telegram support account
      User -> Bool
is_support_1 :: Bool,
      -- | If non-empty, it contains a human-readable description of the reason why access to this user must be restricted
      User -> T
restriction_reason_1 :: T,
      -- | True, if many users reported this user as a scam
      User -> Bool
is_scam_1 :: Bool,
      -- | If false, the user is inaccessible, and the only information known about the user is inside this class. It can't be passed to any method except GetUser 
      User -> Bool
have_access_1 :: Bool,
      -- | Type of the user 
      User -> UserType
type_1 :: UserType,
      -- | IETF language tag of the user's language; only available to bots
      User -> T
language_code_1 :: T
    }
  deriving (I32 -> User -> ShowS
[User] -> ShowS
User -> String
(I32 -> User -> ShowS)
-> (User -> String) -> ([User] -> ShowS) -> Show User
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [User] -> ShowS
$cshowList :: [User] -> ShowS
show :: User -> String
$cshow :: User -> String
showsPrec :: I32 -> User -> ShowS
$cshowsPrec :: I32 -> User -> ShowS
Show, User -> User -> Bool
(User -> User -> Bool) -> (User -> User -> Bool) -> Eq User
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: User -> User -> Bool
$c/= :: User -> User -> Bool
== :: User -> User -> Bool
$c== :: User -> User -> Bool
Eq, (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)
data UserFullInfo
  = -- | Contains full information about a user (except the full list of profile photos) 
  UserFullInfo
    { -- | True, if the user is blacklisted by the current user
      UserFullInfo -> Bool
is_blocked_1 :: Bool,
      -- | True, if the user can be called 
      UserFullInfo -> Bool
can_be_called_1 :: Bool,
      -- | True, if the user can't be called due to their privacy settings
      UserFullInfo -> Bool
has_private_calls_1 :: Bool,
      -- | True, if the current user needs to explicitly allow to share their phone number with the user when the method addContact is used
      UserFullInfo -> Bool
need_phone_number_privacy_exception_1 :: Bool,
      -- | A short user bio 
      UserFullInfo -> T
bio_1 :: T,
      -- | For bots, the text that is included with the link when users share the bot 
      UserFullInfo -> T
share_text_1 :: T,
      -- | Number of group chats where both the other user and the current user are a member; 0 for the current user 
      UserFullInfo -> I32
group_in_common_count_1 :: I32,
      -- | If the user is a bot, information about the bot; may be null
      UserFullInfo -> BotInfo
bot_info_1 :: BotInfo
    }
  deriving (I32 -> UserFullInfo -> ShowS
[UserFullInfo] -> ShowS
UserFullInfo -> String
(I32 -> UserFullInfo -> ShowS)
-> (UserFullInfo -> String)
-> ([UserFullInfo] -> ShowS)
-> Show UserFullInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserFullInfo] -> ShowS
$cshowList :: [UserFullInfo] -> ShowS
show :: UserFullInfo -> String
$cshow :: UserFullInfo -> String
showsPrec :: I32 -> UserFullInfo -> ShowS
$cshowsPrec :: I32 -> UserFullInfo -> ShowS
Show, UserFullInfo -> UserFullInfo -> Bool
(UserFullInfo -> UserFullInfo -> Bool)
-> (UserFullInfo -> UserFullInfo -> Bool) -> Eq UserFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserFullInfo -> UserFullInfo -> Bool
$c/= :: UserFullInfo -> UserFullInfo -> Bool
== :: UserFullInfo -> UserFullInfo -> Bool
$c== :: UserFullInfo -> UserFullInfo -> Bool
Eq, (forall x. UserFullInfo -> Rep UserFullInfo x)
-> (forall x. Rep UserFullInfo x -> UserFullInfo)
-> Generic UserFullInfo
forall x. Rep UserFullInfo x -> UserFullInfo
forall x. UserFullInfo -> Rep UserFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserFullInfo x -> UserFullInfo
$cfrom :: forall x. UserFullInfo -> Rep UserFullInfo x
Generic)
data UserProfilePhoto
  = -- | Contains full information about a user profile photo 
  UserProfilePhoto
    { -- | Unique user profile photo identifier 
      UserProfilePhoto -> I64
id_1 :: I64,
      -- | Point in time (Unix timestamp) when the photo has been added 
      UserProfilePhoto -> I32
added_date_1 :: I32,
      -- | Available variants of the user photo, in different sizes
      UserProfilePhoto -> [PhotoSize]
sizes_1 :: ([]) (PhotoSize)
    }
  deriving (I32 -> UserProfilePhoto -> ShowS
[UserProfilePhoto] -> ShowS
UserProfilePhoto -> String
(I32 -> UserProfilePhoto -> ShowS)
-> (UserProfilePhoto -> String)
-> ([UserProfilePhoto] -> ShowS)
-> Show UserProfilePhoto
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserProfilePhoto] -> ShowS
$cshowList :: [UserProfilePhoto] -> ShowS
show :: UserProfilePhoto -> String
$cshow :: UserProfilePhoto -> String
showsPrec :: I32 -> UserProfilePhoto -> ShowS
$cshowsPrec :: I32 -> UserProfilePhoto -> ShowS
Show, UserProfilePhoto -> UserProfilePhoto -> Bool
(UserProfilePhoto -> UserProfilePhoto -> Bool)
-> (UserProfilePhoto -> UserProfilePhoto -> Bool)
-> Eq UserProfilePhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserProfilePhoto -> UserProfilePhoto -> Bool
$c/= :: UserProfilePhoto -> UserProfilePhoto -> Bool
== :: UserProfilePhoto -> UserProfilePhoto -> Bool
$c== :: UserProfilePhoto -> UserProfilePhoto -> Bool
Eq, (forall x. UserProfilePhoto -> Rep UserProfilePhoto x)
-> (forall x. Rep UserProfilePhoto x -> UserProfilePhoto)
-> Generic UserProfilePhoto
forall x. Rep UserProfilePhoto x -> UserProfilePhoto
forall x. UserProfilePhoto -> Rep UserProfilePhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserProfilePhoto x -> UserProfilePhoto
$cfrom :: forall x. UserProfilePhoto -> Rep UserProfilePhoto x
Generic)
data UserProfilePhotos
  = -- | Contains part of the list of user photos 
  UserProfilePhotos
    { -- | Total number of user profile photos 
      UserProfilePhotos -> I32
total_count_1 :: I32,
      -- | A list of photos
      UserProfilePhotos -> [UserProfilePhoto]
photos_1 :: ([]) (UserProfilePhoto)
    }
  deriving (I32 -> UserProfilePhotos -> ShowS
[UserProfilePhotos] -> ShowS
UserProfilePhotos -> String
(I32 -> UserProfilePhotos -> ShowS)
-> (UserProfilePhotos -> String)
-> ([UserProfilePhotos] -> ShowS)
-> Show UserProfilePhotos
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserProfilePhotos] -> ShowS
$cshowList :: [UserProfilePhotos] -> ShowS
show :: UserProfilePhotos -> String
$cshow :: UserProfilePhotos -> String
showsPrec :: I32 -> UserProfilePhotos -> ShowS
$cshowsPrec :: I32 -> UserProfilePhotos -> ShowS
Show, UserProfilePhotos -> UserProfilePhotos -> Bool
(UserProfilePhotos -> UserProfilePhotos -> Bool)
-> (UserProfilePhotos -> UserProfilePhotos -> Bool)
-> Eq UserProfilePhotos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserProfilePhotos -> UserProfilePhotos -> Bool
$c/= :: UserProfilePhotos -> UserProfilePhotos -> Bool
== :: UserProfilePhotos -> UserProfilePhotos -> Bool
$c== :: UserProfilePhotos -> UserProfilePhotos -> Bool
Eq, (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)
data Users
  = -- | Represents a list of users 
  Users
    { -- | Approximate total count of users found 
      Users -> I32
total_count_1 :: I32,
      -- | A list of user identifiers
      Users -> [I32]
user_ids_1 :: ([]) (I32)
    }
  deriving (I32 -> Users -> ShowS
[Users] -> ShowS
Users -> String
(I32 -> Users -> ShowS)
-> (Users -> String) -> ([Users] -> ShowS) -> Show Users
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Users] -> ShowS
$cshowList :: [Users] -> ShowS
show :: Users -> String
$cshow :: Users -> String
showsPrec :: I32 -> Users -> ShowS
$cshowsPrec :: I32 -> Users -> ShowS
Show, Users -> Users -> Bool
(Users -> Users -> Bool) -> (Users -> Users -> Bool) -> Eq Users
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Users -> Users -> Bool
$c/= :: Users -> Users -> Bool
== :: Users -> Users -> Bool
$c== :: Users -> Users -> Bool
Eq, (forall x. Users -> Rep Users x)
-> (forall x. Rep Users x -> Users) -> Generic Users
forall x. Rep Users x -> Users
forall x. Users -> Rep Users x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Users x -> Users
$cfrom :: forall x. Users -> Rep Users x
Generic)
data ChatAdministrator
  = -- | Contains information about a chat administrator 
  ChatAdministrator
    { -- | User identifier of the administrator 
      ChatAdministrator -> I32
user_id_1 :: I32,
      -- | Custom title of the administrator 
      ChatAdministrator -> T
custom_title_1 :: T,
      -- | True, if the user is the owner of the chat
      ChatAdministrator -> Bool
is_owner_1 :: Bool
    }
  deriving (I32 -> ChatAdministrator -> ShowS
[ChatAdministrator] -> ShowS
ChatAdministrator -> String
(I32 -> ChatAdministrator -> ShowS)
-> (ChatAdministrator -> String)
-> ([ChatAdministrator] -> ShowS)
-> Show ChatAdministrator
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatAdministrator] -> ShowS
$cshowList :: [ChatAdministrator] -> ShowS
show :: ChatAdministrator -> String
$cshow :: ChatAdministrator -> String
showsPrec :: I32 -> ChatAdministrator -> ShowS
$cshowsPrec :: I32 -> ChatAdministrator -> ShowS
Show, ChatAdministrator -> ChatAdministrator -> Bool
(ChatAdministrator -> ChatAdministrator -> Bool)
-> (ChatAdministrator -> ChatAdministrator -> Bool)
-> Eq ChatAdministrator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatAdministrator -> ChatAdministrator -> Bool
$c/= :: ChatAdministrator -> ChatAdministrator -> Bool
== :: ChatAdministrator -> ChatAdministrator -> Bool
$c== :: ChatAdministrator -> ChatAdministrator -> Bool
Eq, (forall x. ChatAdministrator -> Rep ChatAdministrator x)
-> (forall x. Rep ChatAdministrator x -> ChatAdministrator)
-> Generic ChatAdministrator
forall x. Rep ChatAdministrator x -> ChatAdministrator
forall x. ChatAdministrator -> Rep ChatAdministrator x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatAdministrator x -> ChatAdministrator
$cfrom :: forall x. ChatAdministrator -> Rep ChatAdministrator x
Generic)
data ChatAdministrators
  = -- | Represents a list of chat administrators 
  ChatAdministrators
    { -- | A list of chat administrators
      ChatAdministrators -> [ChatAdministrator]
administrators_1 :: ([]) (ChatAdministrator)
    }
  deriving (I32 -> ChatAdministrators -> ShowS
[ChatAdministrators] -> ShowS
ChatAdministrators -> String
(I32 -> ChatAdministrators -> ShowS)
-> (ChatAdministrators -> String)
-> ([ChatAdministrators] -> ShowS)
-> Show ChatAdministrators
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatAdministrators] -> ShowS
$cshowList :: [ChatAdministrators] -> ShowS
show :: ChatAdministrators -> String
$cshow :: ChatAdministrators -> String
showsPrec :: I32 -> ChatAdministrators -> ShowS
$cshowsPrec :: I32 -> ChatAdministrators -> ShowS
Show, ChatAdministrators -> ChatAdministrators -> Bool
(ChatAdministrators -> ChatAdministrators -> Bool)
-> (ChatAdministrators -> ChatAdministrators -> Bool)
-> Eq ChatAdministrators
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatAdministrators -> ChatAdministrators -> Bool
$c/= :: ChatAdministrators -> ChatAdministrators -> Bool
== :: ChatAdministrators -> ChatAdministrators -> Bool
$c== :: ChatAdministrators -> ChatAdministrators -> Bool
Eq, (forall x. ChatAdministrators -> Rep ChatAdministrators x)
-> (forall x. Rep ChatAdministrators x -> ChatAdministrators)
-> Generic ChatAdministrators
forall x. Rep ChatAdministrators x -> ChatAdministrators
forall x. ChatAdministrators -> Rep ChatAdministrators x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatAdministrators x -> ChatAdministrators
$cfrom :: forall x. ChatAdministrators -> Rep ChatAdministrators x
Generic)
data ChatPermissions
  = -- | Describes actions that a user is allowed to take in a chat
  ChatPermissions
    { -- | True, if the user can send text messages, contacts, locations, and venues
      ChatPermissions -> Bool
can_send_messages_1 :: Bool,
      -- | True, if the user can send audio files, documents, photos, videos, video notes, and voice notes. Implies can_send_messages permissions
      ChatPermissions -> Bool
can_send_media_messages_1 :: Bool,
      -- | True, if the user can send polls. Implies can_send_messages permissions
      ChatPermissions -> Bool
can_send_polls_1 :: Bool,
      -- | True, if the user can send animations, games, and stickers and use inline bots. Implies can_send_messages permissions
      ChatPermissions -> Bool
can_send_other_messages_1 :: Bool,
      -- | True, if the user may add a web page preview to their messages. Implies can_send_messages permissions
      ChatPermissions -> Bool
can_add_web_page_previews_1 :: Bool,
      -- | True, if the user can change the chat title, photo, and other settings
      ChatPermissions -> Bool
can_change_info_1 :: Bool,
      -- | True, if the user can invite new users to the chat
      ChatPermissions -> Bool
can_invite_users_1 :: Bool,
      -- | True, if the user can pin messages
      ChatPermissions -> Bool
can_pin_messages_1 :: Bool
    }
  deriving (I32 -> ChatPermissions -> ShowS
[ChatPermissions] -> ShowS
ChatPermissions -> String
(I32 -> ChatPermissions -> ShowS)
-> (ChatPermissions -> String)
-> ([ChatPermissions] -> ShowS)
-> Show ChatPermissions
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatPermissions] -> ShowS
$cshowList :: [ChatPermissions] -> ShowS
show :: ChatPermissions -> String
$cshow :: ChatPermissions -> String
showsPrec :: I32 -> ChatPermissions -> ShowS
$cshowsPrec :: I32 -> ChatPermissions -> ShowS
Show, ChatPermissions -> ChatPermissions -> Bool
(ChatPermissions -> ChatPermissions -> Bool)
-> (ChatPermissions -> ChatPermissions -> Bool)
-> Eq ChatPermissions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatPermissions -> ChatPermissions -> Bool
$c/= :: ChatPermissions -> ChatPermissions -> Bool
== :: ChatPermissions -> ChatPermissions -> Bool
$c== :: ChatPermissions -> ChatPermissions -> Bool
Eq, (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)
-- | Provides information about the status of a member in a chat
data ChatMemberStatus
  = -- | The user is the owner of a chat and has all the administrator privileges
  ChatMemberStatusCreator
    { -- | A custom title of the owner; 0-16 characters without emojis; applicable to supergroups only
      ChatMemberStatus -> T
custom_title_1 :: T,
      -- | True, if the user is a member of the chat
      ChatMemberStatus -> Bool
is_member_1 :: Bool
    }
  | -- | The user is a member of a chat and has some additional privileges. In basic groups, administrators can edit and delete messages sent by others, add new members, and ban unprivileged members. In supergroups and channels, there are more detailed options for administrator privileges
  ChatMemberStatusAdministrator
    { -- | A custom title of the administrator; 0-16 characters without emojis; applicable to supergroups only
      ChatMemberStatus -> T
custom_title_2 :: T,
      -- | True, if the current user can edit the administrator privileges for the called user
      ChatMemberStatus -> Bool
can_be_edited_2 :: Bool,
      -- | True, if the administrator can change the chat title, photo, and other settings
      ChatMemberStatus -> Bool
can_change_info_2 :: Bool,
      -- | True, if the administrator can create channel posts; applicable to channels only
      ChatMemberStatus -> Bool
can_post_messages_2 :: Bool,
      -- | True, if the administrator can edit messages of other users and pin messages; applicable to channels only
      ChatMemberStatus -> Bool
can_edit_messages_2 :: Bool,
      -- | True, if the administrator can delete messages of other users
      ChatMemberStatus -> Bool
can_delete_messages_2 :: Bool,
      -- | True, if the administrator can invite new users to the chat
      ChatMemberStatus -> Bool
can_invite_users_2 :: Bool,
      -- | True, if the administrator can restrict, ban, or unban chat members
      ChatMemberStatus -> Bool
can_restrict_members_2 :: Bool,
      -- | True, if the administrator can pin messages; applicable to groups only
      ChatMemberStatus -> Bool
can_pin_messages_2 :: Bool,
      -- | True, if the administrator can add new administrators with a subset of their own privileges or demote administrators that were directly or indirectly promoted by them
      ChatMemberStatus -> Bool
can_promote_members_2 :: Bool
    }
  | -- | The user is a member of a chat, without any additional privileges or restrictions
  ChatMemberStatusMember
    { 
    }
  | -- | The user is under certain restrictions in the chat. Not supported in basic groups and channels
  ChatMemberStatusRestricted
    { -- | True, if the user is a member of the chat
      ChatMemberStatus -> Bool
is_member_4 :: Bool,
      -- | Point in time (Unix timestamp) when restrictions will be lifted from the user; 0 if never. If the user is restricted for more than 366 days or for less than 30 seconds from the current time, the user is considered to be restricted forever
      ChatMemberStatus -> I32
restricted_until_date_4 :: I32,
      -- | User permissions in the chat
      ChatMemberStatus -> ChatPermissions
permissions_4 :: ChatPermissions
    }
  | -- | The user is not a chat member
  ChatMemberStatusLeft
    { 
    }
  | -- | The user was banned (and hence is not a member of the chat). Implies the user can't return to the chat or view messages
  ChatMemberStatusBanned
    { -- | Point in time (Unix timestamp) when the user will be unbanned; 0 if never. If the user is banned for more than 366 days or for less than 30 seconds from the current time, the user is considered to be banned forever
      ChatMemberStatus -> I32
banned_until_date_6 :: I32
    }
  deriving (I32 -> ChatMemberStatus -> ShowS
[ChatMemberStatus] -> ShowS
ChatMemberStatus -> String
(I32 -> ChatMemberStatus -> ShowS)
-> (ChatMemberStatus -> String)
-> ([ChatMemberStatus] -> ShowS)
-> Show ChatMemberStatus
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMemberStatus] -> ShowS
$cshowList :: [ChatMemberStatus] -> ShowS
show :: ChatMemberStatus -> String
$cshow :: ChatMemberStatus -> String
showsPrec :: I32 -> ChatMemberStatus -> ShowS
$cshowsPrec :: I32 -> ChatMemberStatus -> ShowS
Show, ChatMemberStatus -> ChatMemberStatus -> Bool
(ChatMemberStatus -> ChatMemberStatus -> Bool)
-> (ChatMemberStatus -> ChatMemberStatus -> Bool)
-> Eq ChatMemberStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatMemberStatus -> ChatMemberStatus -> Bool
$c/= :: ChatMemberStatus -> ChatMemberStatus -> Bool
== :: ChatMemberStatus -> ChatMemberStatus -> Bool
$c== :: ChatMemberStatus -> ChatMemberStatus -> Bool
Eq, (forall x. ChatMemberStatus -> Rep ChatMemberStatus x)
-> (forall x. Rep ChatMemberStatus x -> ChatMemberStatus)
-> Generic ChatMemberStatus
forall x. Rep ChatMemberStatus x -> ChatMemberStatus
forall x. ChatMemberStatus -> Rep ChatMemberStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatMemberStatus x -> ChatMemberStatus
$cfrom :: forall x. ChatMemberStatus -> Rep ChatMemberStatus x
Generic)
data ChatMember
  = -- | A user with information about joining/leaving a chat 
  ChatMember
    { -- | User identifier of the chat member 
      ChatMember -> I32
user_id_1 :: I32,
      -- | Identifier of a user that invited/promoted/banned this member in the chat; 0 if unknown
      ChatMember -> I32
inviter_user_id_1 :: I32,
      -- | Point in time (Unix timestamp) when the user joined a chat 
      ChatMember -> I32
joined_chat_date_1 :: I32,
      -- | Status of the member in the chat 
      ChatMember -> ChatMemberStatus
status_1 :: ChatMemberStatus,
      -- | If the user is a bot, information about the bot; may be null. Can be null even for a bot if the bot is not a chat member
      ChatMember -> BotInfo
bot_info_1 :: BotInfo
    }
  deriving (I32 -> ChatMember -> ShowS
[ChatMember] -> ShowS
ChatMember -> String
(I32 -> ChatMember -> ShowS)
-> (ChatMember -> String)
-> ([ChatMember] -> ShowS)
-> Show ChatMember
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMember] -> ShowS
$cshowList :: [ChatMember] -> ShowS
show :: ChatMember -> String
$cshow :: ChatMember -> String
showsPrec :: I32 -> ChatMember -> ShowS
$cshowsPrec :: I32 -> ChatMember -> ShowS
Show, ChatMember -> ChatMember -> Bool
(ChatMember -> ChatMember -> Bool)
-> (ChatMember -> ChatMember -> Bool) -> Eq ChatMember
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatMember -> ChatMember -> Bool
$c/= :: ChatMember -> ChatMember -> Bool
== :: ChatMember -> ChatMember -> Bool
$c== :: ChatMember -> ChatMember -> Bool
Eq, (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)
data ChatMembers
  = -- | Contains a list of chat members 
  ChatMembers
    { -- | Approximate total count of chat members found 
      ChatMembers -> I32
total_count_1 :: I32,
      -- | A list of chat members
      ChatMembers -> [ChatMember]
members_1 :: ([]) (ChatMember)
    }
  deriving (I32 -> ChatMembers -> ShowS
[ChatMembers] -> ShowS
ChatMembers -> String
(I32 -> ChatMembers -> ShowS)
-> (ChatMembers -> String)
-> ([ChatMembers] -> ShowS)
-> Show ChatMembers
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMembers] -> ShowS
$cshowList :: [ChatMembers] -> ShowS
show :: ChatMembers -> String
$cshow :: ChatMembers -> String
showsPrec :: I32 -> ChatMembers -> ShowS
$cshowsPrec :: I32 -> ChatMembers -> ShowS
Show, ChatMembers -> ChatMembers -> Bool
(ChatMembers -> ChatMembers -> Bool)
-> (ChatMembers -> ChatMembers -> Bool) -> Eq ChatMembers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatMembers -> ChatMembers -> Bool
$c/= :: ChatMembers -> ChatMembers -> Bool
== :: ChatMembers -> ChatMembers -> Bool
$c== :: ChatMembers -> ChatMembers -> Bool
Eq, (forall x. ChatMembers -> Rep ChatMembers x)
-> (forall x. Rep ChatMembers x -> ChatMembers)
-> Generic ChatMembers
forall x. Rep ChatMembers x -> ChatMembers
forall x. ChatMembers -> Rep ChatMembers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatMembers x -> ChatMembers
$cfrom :: forall x. ChatMembers -> Rep ChatMembers x
Generic)
-- | Specifies the kind of chat members to return in searchChatMembers
data ChatMembersFilter
  = -- | Returns contacts of the user
  ChatMembersFilterContacts
    { 
    }
  | -- | Returns the owner and administrators
  ChatMembersFilterAdministrators
    { 
    }
  | -- | Returns all chat members, including restricted chat members
  ChatMembersFilterMembers
    { 
    }
  | -- | Returns users under certain restrictions in the chat; can be used only by administrators in a supergroup
  ChatMembersFilterRestricted
    { 
    }
  | -- | Returns users banned from the chat; can be used only by administrators in a supergroup or in a channel
  ChatMembersFilterBanned
    { 
    }
  | -- | Returns bot members of the chat
  ChatMembersFilterBots
    { 
    }
  deriving (I32 -> ChatMembersFilter -> ShowS
[ChatMembersFilter] -> ShowS
ChatMembersFilter -> String
(I32 -> ChatMembersFilter -> ShowS)
-> (ChatMembersFilter -> String)
-> ([ChatMembersFilter] -> ShowS)
-> Show ChatMembersFilter
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatMembersFilter] -> ShowS
$cshowList :: [ChatMembersFilter] -> ShowS
show :: ChatMembersFilter -> String
$cshow :: ChatMembersFilter -> String
showsPrec :: I32 -> ChatMembersFilter -> ShowS
$cshowsPrec :: I32 -> ChatMembersFilter -> ShowS
Show, ChatMembersFilter -> ChatMembersFilter -> Bool
(ChatMembersFilter -> ChatMembersFilter -> Bool)
-> (ChatMembersFilter -> ChatMembersFilter -> Bool)
-> Eq ChatMembersFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatMembersFilter -> ChatMembersFilter -> Bool
$c/= :: ChatMembersFilter -> ChatMembersFilter -> Bool
== :: ChatMembersFilter -> ChatMembersFilter -> Bool
$c== :: ChatMembersFilter -> ChatMembersFilter -> Bool
Eq, (forall x. ChatMembersFilter -> Rep ChatMembersFilter x)
-> (forall x. Rep ChatMembersFilter x -> ChatMembersFilter)
-> Generic ChatMembersFilter
forall x. Rep ChatMembersFilter x -> ChatMembersFilter
forall x. ChatMembersFilter -> Rep ChatMembersFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatMembersFilter x -> ChatMembersFilter
$cfrom :: forall x. ChatMembersFilter -> Rep ChatMembersFilter x
Generic)
-- | Specifies the kind of chat members to return in getSupergroupMembers
data SupergroupMembersFilter
  = -- | Returns recently active users in reverse chronological order
  SupergroupMembersFilterRecent
    { 
    }
  | -- | Returns contacts of the user, which are members of the supergroup or channel 
  SupergroupMembersFilterContacts
    { -- | Query to search for
      SupergroupMembersFilter -> T
query_2 :: T
    }
  | -- | Returns the owner and administrators
  SupergroupMembersFilterAdministrators
    { 
    }
  | -- | Used to search for supergroup or channel members via a (string) query 
  SupergroupMembersFilterSearch
    { -- | Query to search for
      SupergroupMembersFilter -> T
query_4 :: T
    }
  | -- | Returns restricted supergroup members; can be used only by administrators 
  SupergroupMembersFilterRestricted
    { -- | Query to search for
      SupergroupMembersFilter -> T
query_5 :: T
    }
  | -- | Returns users banned from the supergroup or channel; can be used only by administrators 
  SupergroupMembersFilterBanned
    { -- | Query to search for
      SupergroupMembersFilter -> T
query_6 :: T
    }
  | -- | Returns bot members of the supergroup or channel
  SupergroupMembersFilterBots
    { 
    }
  deriving (I32 -> SupergroupMembersFilter -> ShowS
[SupergroupMembersFilter] -> ShowS
SupergroupMembersFilter -> String
(I32 -> SupergroupMembersFilter -> ShowS)
-> (SupergroupMembersFilter -> String)
-> ([SupergroupMembersFilter] -> ShowS)
-> Show SupergroupMembersFilter
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SupergroupMembersFilter] -> ShowS
$cshowList :: [SupergroupMembersFilter] -> ShowS
show :: SupergroupMembersFilter -> String
$cshow :: SupergroupMembersFilter -> String
showsPrec :: I32 -> SupergroupMembersFilter -> ShowS
$cshowsPrec :: I32 -> SupergroupMembersFilter -> ShowS
Show, SupergroupMembersFilter -> SupergroupMembersFilter -> Bool
(SupergroupMembersFilter -> SupergroupMembersFilter -> Bool)
-> (SupergroupMembersFilter -> SupergroupMembersFilter -> Bool)
-> Eq SupergroupMembersFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SupergroupMembersFilter -> SupergroupMembersFilter -> Bool
$c/= :: SupergroupMembersFilter -> SupergroupMembersFilter -> Bool
== :: SupergroupMembersFilter -> SupergroupMembersFilter -> Bool
$c== :: SupergroupMembersFilter -> SupergroupMembersFilter -> Bool
Eq, (forall x.
 SupergroupMembersFilter -> Rep SupergroupMembersFilter x)
-> (forall x.
    Rep SupergroupMembersFilter x -> SupergroupMembersFilter)
-> Generic SupergroupMembersFilter
forall x. Rep SupergroupMembersFilter x -> SupergroupMembersFilter
forall x. SupergroupMembersFilter -> Rep SupergroupMembersFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SupergroupMembersFilter x -> SupergroupMembersFilter
$cfrom :: forall x. SupergroupMembersFilter -> Rep SupergroupMembersFilter x
Generic)
data BasicGroup
  = -- | Represents a basic group of 0-200 users (must be upgraded to a supergroup to accommodate more than 200 users)
  BasicGroup
    { -- | Group identifier
      BasicGroup -> I32
id_1 :: I32,
      -- | Number of members in the group
      BasicGroup -> I32
member_count_1 :: I32,
      -- | Status of the current user in the group
      BasicGroup -> ChatMemberStatus
status_1 :: ChatMemberStatus,
      -- | True, if the group is active
      BasicGroup -> Bool
is_active_1 :: Bool,
      -- | Identifier of the supergroup to which this group was upgraded; 0 if none
      BasicGroup -> I32
upgraded_to_supergroup_id_1 :: I32
    }
  deriving (I32 -> BasicGroup -> ShowS
[BasicGroup] -> ShowS
BasicGroup -> String
(I32 -> BasicGroup -> ShowS)
-> (BasicGroup -> String)
-> ([BasicGroup] -> ShowS)
-> Show BasicGroup
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BasicGroup] -> ShowS
$cshowList :: [BasicGroup] -> ShowS
show :: BasicGroup -> String
$cshow :: BasicGroup -> String
showsPrec :: I32 -> BasicGroup -> ShowS
$cshowsPrec :: I32 -> BasicGroup -> ShowS
Show, BasicGroup -> BasicGroup -> Bool
(BasicGroup -> BasicGroup -> Bool)
-> (BasicGroup -> BasicGroup -> Bool) -> Eq BasicGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicGroup -> BasicGroup -> Bool
$c/= :: BasicGroup -> BasicGroup -> Bool
== :: BasicGroup -> BasicGroup -> Bool
$c== :: BasicGroup -> BasicGroup -> Bool
Eq, (forall x. BasicGroup -> Rep BasicGroup x)
-> (forall x. Rep BasicGroup x -> BasicGroup) -> Generic BasicGroup
forall x. Rep BasicGroup x -> BasicGroup
forall x. BasicGroup -> Rep BasicGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BasicGroup x -> BasicGroup
$cfrom :: forall x. BasicGroup -> Rep BasicGroup x
Generic)
data BasicGroupFullInfo
  = -- | Contains full information about a basic group 
  BasicGroupFullInfo
    { -- | Contains full information about a basic group 
      BasicGroupFullInfo -> T
description_1 :: T,
      -- | User identifier of the creator of the group; 0 if unknown 
      BasicGroupFullInfo -> I32
creator_user_id_1 :: I32,
      -- | Group members 
      BasicGroupFullInfo -> [ChatMember]
members_1 :: ([]) (ChatMember),
      -- | Invite link for this group; available only after it has been generated at least once and only for the group creator
      BasicGroupFullInfo -> T
invite_link_1 :: T
    }
  deriving (I32 -> BasicGroupFullInfo -> ShowS
[BasicGroupFullInfo] -> ShowS
BasicGroupFullInfo -> String
(I32 -> BasicGroupFullInfo -> ShowS)
-> (BasicGroupFullInfo -> String)
-> ([BasicGroupFullInfo] -> ShowS)
-> Show BasicGroupFullInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BasicGroupFullInfo] -> ShowS
$cshowList :: [BasicGroupFullInfo] -> ShowS
show :: BasicGroupFullInfo -> String
$cshow :: BasicGroupFullInfo -> String
showsPrec :: I32 -> BasicGroupFullInfo -> ShowS
$cshowsPrec :: I32 -> BasicGroupFullInfo -> ShowS
Show, BasicGroupFullInfo -> BasicGroupFullInfo -> Bool
(BasicGroupFullInfo -> BasicGroupFullInfo -> Bool)
-> (BasicGroupFullInfo -> BasicGroupFullInfo -> Bool)
-> Eq BasicGroupFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicGroupFullInfo -> BasicGroupFullInfo -> Bool
$c/= :: BasicGroupFullInfo -> BasicGroupFullInfo -> Bool
== :: BasicGroupFullInfo -> BasicGroupFullInfo -> Bool
$c== :: BasicGroupFullInfo -> BasicGroupFullInfo -> Bool
Eq, (forall x. BasicGroupFullInfo -> Rep BasicGroupFullInfo x)
-> (forall x. Rep BasicGroupFullInfo x -> BasicGroupFullInfo)
-> Generic BasicGroupFullInfo
forall x. Rep BasicGroupFullInfo x -> BasicGroupFullInfo
forall x. BasicGroupFullInfo -> Rep BasicGroupFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BasicGroupFullInfo x -> BasicGroupFullInfo
$cfrom :: forall x. BasicGroupFullInfo -> Rep BasicGroupFullInfo x
Generic)
data Supergroup
  = -- | Represents a supergroup or channel with zero or more members (subscribers in the case of channels). From the point of view of the system, a channel is a special kind of a supergroup: only administrators can post and see the list of members, and posts from all administrators use the name and photo of the channel instead of individual names and profile photos. Unlike supergroups, channels can have an unlimited number of subscribers
  Supergroup
    { -- | Supergroup or channel identifier
      Supergroup -> I32
id_1 :: I32,
      -- | Username of the supergroup or channel; empty for private supergroups or channels
      Supergroup -> T
username_1 :: T,
      -- | Point in time (Unix timestamp) when the current user joined, or the point in time when the supergroup or channel was created, in case the user is not a member
      Supergroup -> I32
date_1 :: I32,
      -- | Status of the current user in the supergroup or channel; custom title will be always empty
      Supergroup -> ChatMemberStatus
status_1 :: ChatMemberStatus,
      -- | Number of members in the supergroup or channel; 0 if unknown. Currently it is guaranteed to be known only if the supergroup or channel was found through SearchPublicChats
      Supergroup -> I32
member_count_1 :: I32,
      -- | True, if the channel has a discussion group, or the supergroup is the designated discussion group for a channel
      Supergroup -> Bool
has_linked_chat_1 :: Bool,
      -- | True, if the supergroup is connected to a location, i.e. the supergroup is a location-based supergroup
      Supergroup -> Bool
has_location_1 :: Bool,
      -- | True, if messages sent to the channel should contain information about the sender. This field is only applicable to channels
      Supergroup -> Bool
sign_messages_1 :: Bool,
      -- | True, if the slow mode is enabled in the supergroup
      Supergroup -> Bool
is_slow_mode_enabled_1 :: Bool,
      -- | True, if the supergroup is a channel
      Supergroup -> Bool
is_channel_1 :: Bool,
      -- | True, if the supergroup or channel is verified
      Supergroup -> Bool
is_verified_1 :: Bool,
      -- | If non-empty, contains a human-readable description of the reason why access to this supergroup or channel must be restricted
      Supergroup -> T
restriction_reason_1 :: T,
      -- | True, if many users reported this supergroup as a scam
      Supergroup -> Bool
is_scam_1 :: Bool
    }
  deriving (I32 -> Supergroup -> ShowS
[Supergroup] -> ShowS
Supergroup -> String
(I32 -> Supergroup -> ShowS)
-> (Supergroup -> String)
-> ([Supergroup] -> ShowS)
-> Show Supergroup
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Supergroup] -> ShowS
$cshowList :: [Supergroup] -> ShowS
show :: Supergroup -> String
$cshow :: Supergroup -> String
showsPrec :: I32 -> Supergroup -> ShowS
$cshowsPrec :: I32 -> Supergroup -> ShowS
Show, Supergroup -> Supergroup -> Bool
(Supergroup -> Supergroup -> Bool)
-> (Supergroup -> Supergroup -> Bool) -> Eq Supergroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Supergroup -> Supergroup -> Bool
$c/= :: Supergroup -> Supergroup -> Bool
== :: Supergroup -> Supergroup -> Bool
$c== :: Supergroup -> Supergroup -> Bool
Eq, (forall x. Supergroup -> Rep Supergroup x)
-> (forall x. Rep Supergroup x -> Supergroup) -> Generic Supergroup
forall x. Rep Supergroup x -> Supergroup
forall x. Supergroup -> Rep Supergroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Supergroup x -> Supergroup
$cfrom :: forall x. Supergroup -> Rep Supergroup x
Generic)
data SupergroupFullInfo
  = -- | Contains full information about a supergroup or channel
  SupergroupFullInfo
    { -- | Contains full information about a supergroup or channel
      SupergroupFullInfo -> T
description_1 :: T,
      -- | Number of members in the supergroup or channel; 0 if unknown
      SupergroupFullInfo -> I32
member_count_1 :: I32,
      -- | Number of privileged users in the supergroup or channel; 0 if unknown
      SupergroupFullInfo -> I32
administrator_count_1 :: I32,
      -- | Number of restricted users in the supergroup; 0 if unknown
      SupergroupFullInfo -> I32
restricted_count_1 :: I32,
      -- | Number of users banned from chat; 0 if unknown
      SupergroupFullInfo -> I32
banned_count_1 :: I32,
      -- | Chat identifier of a discussion group for the channel, or a channel, for which the supergroup is the designated discussion group; 0 if none or unknown
      SupergroupFullInfo -> I32
linked_chat_id_1 :: I53,
      -- | Delay between consecutive sent messages for non-administrator supergroup members, in seconds
      SupergroupFullInfo -> I32
slow_mode_delay_1 :: I32,
      -- | Time left before next message can be sent in the supergroup, in seconds. An updateSupergroupFullInfo update is not triggered when value of this field changes, but both new and old values are non-zero
      SupergroupFullInfo -> Double
slow_mode_delay_expires_in_1 :: Double,
      -- | True, if members of the chat can be retrieved
      SupergroupFullInfo -> Bool
can_get_members_1 :: Bool,
      -- | True, if the chat username can be changed
      SupergroupFullInfo -> Bool
can_set_username_1 :: Bool,
      -- | True, if the supergroup sticker set can be changed
      SupergroupFullInfo -> Bool
can_set_sticker_set_1 :: Bool,
      -- | True, if the supergroup location can be changed
      SupergroupFullInfo -> Bool
can_set_location_1 :: Bool,
      -- | True, if the channel statistics is available
      SupergroupFullInfo -> Bool
can_view_statistics_1 :: Bool,
      -- | True, if new chat members will have access to old messages. In public or discussion groups and both public and private channels, old messages are always available, so this option affects only private supergroups without a linked chat. The value of this field is only available for chat administrators
      SupergroupFullInfo -> Bool
is_all_history_available_1 :: Bool,
      -- | Identifier of the supergroup sticker set; 0 if none
      SupergroupFullInfo -> I64
sticker_set_id_1 :: I64,
      -- | Location to which the supergroup is connected; may be null
      SupergroupFullInfo -> ChatLocation
location_1 :: ChatLocation,
      -- | Invite link for this chat
      SupergroupFullInfo -> T
invite_link_1 :: T,
      -- | Identifier of the basic group from which supergroup was upgraded; 0 if none
      SupergroupFullInfo -> I32
upgraded_from_basic_group_id_1 :: I32,
      -- | Identifier of the last message in the basic group from which supergroup was upgraded; 0 if none
      SupergroupFullInfo -> I32
upgraded_from_max_message_id_1 :: I53
    }
  deriving (I32 -> SupergroupFullInfo -> ShowS
[SupergroupFullInfo] -> ShowS
SupergroupFullInfo -> String
(I32 -> SupergroupFullInfo -> ShowS)
-> (SupergroupFullInfo -> String)
-> ([SupergroupFullInfo] -> ShowS)
-> Show SupergroupFullInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SupergroupFullInfo] -> ShowS
$cshowList :: [SupergroupFullInfo] -> ShowS
show :: SupergroupFullInfo -> String
$cshow :: SupergroupFullInfo -> String
showsPrec :: I32 -> SupergroupFullInfo -> ShowS
$cshowsPrec :: I32 -> SupergroupFullInfo -> ShowS
Show, SupergroupFullInfo -> SupergroupFullInfo -> Bool
(SupergroupFullInfo -> SupergroupFullInfo -> Bool)
-> (SupergroupFullInfo -> SupergroupFullInfo -> Bool)
-> Eq SupergroupFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SupergroupFullInfo -> SupergroupFullInfo -> Bool
$c/= :: SupergroupFullInfo -> SupergroupFullInfo -> Bool
== :: SupergroupFullInfo -> SupergroupFullInfo -> Bool
$c== :: SupergroupFullInfo -> SupergroupFullInfo -> Bool
Eq, (forall x. SupergroupFullInfo -> Rep SupergroupFullInfo x)
-> (forall x. Rep SupergroupFullInfo x -> SupergroupFullInfo)
-> Generic SupergroupFullInfo
forall x. Rep SupergroupFullInfo x -> SupergroupFullInfo
forall x. SupergroupFullInfo -> Rep SupergroupFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SupergroupFullInfo x -> SupergroupFullInfo
$cfrom :: forall x. SupergroupFullInfo -> Rep SupergroupFullInfo x
Generic)
-- | Describes the current secret chat state
data SecretChatState
  = -- | The secret chat is not yet created; waiting for the other user to get online
  SecretChatStatePending
    { 
    }
  | -- | The secret chat is ready to use
  SecretChatStateReady
    { 
    }
  | -- | The secret chat is closed
  SecretChatStateClosed
    { 
    }
  deriving (I32 -> SecretChatState -> ShowS
[SecretChatState] -> ShowS
SecretChatState -> String
(I32 -> SecretChatState -> ShowS)
-> (SecretChatState -> String)
-> ([SecretChatState] -> ShowS)
-> Show SecretChatState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecretChatState] -> ShowS
$cshowList :: [SecretChatState] -> ShowS
show :: SecretChatState -> String
$cshow :: SecretChatState -> String
showsPrec :: I32 -> SecretChatState -> ShowS
$cshowsPrec :: I32 -> SecretChatState -> ShowS
Show, SecretChatState -> SecretChatState -> Bool
(SecretChatState -> SecretChatState -> Bool)
-> (SecretChatState -> SecretChatState -> Bool)
-> Eq SecretChatState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecretChatState -> SecretChatState -> Bool
$c/= :: SecretChatState -> SecretChatState -> Bool
== :: SecretChatState -> SecretChatState -> Bool
$c== :: SecretChatState -> SecretChatState -> Bool
Eq, (forall x. SecretChatState -> Rep SecretChatState x)
-> (forall x. Rep SecretChatState x -> SecretChatState)
-> Generic SecretChatState
forall x. Rep SecretChatState x -> SecretChatState
forall x. SecretChatState -> Rep SecretChatState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecretChatState x -> SecretChatState
$cfrom :: forall x. SecretChatState -> Rep SecretChatState x
Generic)
data SecretChat
  = -- | Represents a secret chat
  SecretChat
    { -- | Secret chat identifier
      SecretChat -> I32
id_1 :: I32,
      -- | Identifier of the chat partner
      SecretChat -> I32
user_id_1 :: I32,
      -- | State of the secret chat
      SecretChat -> SecretChatState
state_1 :: SecretChatState,
      -- | True, if the chat was created by the current user; otherwise false
      SecretChat -> Bool
is_outbound_1 :: Bool,
      -- | Current message Time To Live setting (self-destruct timer) for the chat, in seconds
      SecretChat -> I32
ttl_1 :: I32,
      -- | Hash of the currently used key for comparison with the hash of the chat partner's key. This is a string of 36 little-endian bytes, which must be split into groups of 2 bits, each denoting a pixel of one of 4 colors FFFFFF, D5E6F3, 2D5775, and 2F99C9.
      SecretChat -> ByteString64
key_hash_1 :: ByteString64,
      -- | Secret chat layer; determines features supported by the other client. Video notes are supported if the layer >= 66; nested text entities and underline and strikethrough entities are supported if the layer >= 101
      SecretChat -> I32
layer_1 :: I32
    }
  deriving (I32 -> SecretChat -> ShowS
[SecretChat] -> ShowS
SecretChat -> String
(I32 -> SecretChat -> ShowS)
-> (SecretChat -> String)
-> ([SecretChat] -> ShowS)
-> Show SecretChat
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SecretChat] -> ShowS
$cshowList :: [SecretChat] -> ShowS
show :: SecretChat -> String
$cshow :: SecretChat -> String
showsPrec :: I32 -> SecretChat -> ShowS
$cshowsPrec :: I32 -> SecretChat -> ShowS
Show, SecretChat -> SecretChat -> Bool
(SecretChat -> SecretChat -> Bool)
-> (SecretChat -> SecretChat -> Bool) -> Eq SecretChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SecretChat -> SecretChat -> Bool
$c/= :: SecretChat -> SecretChat -> Bool
== :: SecretChat -> SecretChat -> Bool
$c== :: SecretChat -> SecretChat -> Bool
Eq, (forall x. SecretChat -> Rep SecretChat x)
-> (forall x. Rep SecretChat x -> SecretChat) -> Generic SecretChat
forall x. Rep SecretChat x -> SecretChat
forall x. SecretChat -> Rep SecretChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SecretChat x -> SecretChat
$cfrom :: forall x. SecretChat -> Rep SecretChat x
Generic)
-- | Contains information about the origin of a forwarded message
data MessageForwardOrigin
  = -- | The message was originally written by a known user 
  MessageForwardOriginUser
    { -- | Identifier of the user that originally sent the message
      MessageForwardOrigin -> I32
sender_user_id_1 :: I32
    }
  | -- | The message was originally written by a user, which is hidden by their privacy settings 
  MessageForwardOriginHiddenUser
    { -- | Name of the sender
      MessageForwardOrigin -> T
sender_name_2 :: T
    }
  | -- | The message was originally a post in a channel
  MessageForwardOriginChannel
    { -- | Identifier of the chat from which the message was originally forwarded
      MessageForwardOrigin -> I32
chat_id_3 :: I53,
      -- | Message identifier of the original message; 0 if unknown
      MessageForwardOrigin -> I32
message_id_3 :: I53,
      -- | Original post author signature
      MessageForwardOrigin -> T
author_signature_3 :: T
    }
  deriving (I32 -> MessageForwardOrigin -> ShowS
[MessageForwardOrigin] -> ShowS
MessageForwardOrigin -> String
(I32 -> MessageForwardOrigin -> ShowS)
-> (MessageForwardOrigin -> String)
-> ([MessageForwardOrigin] -> ShowS)
-> Show MessageForwardOrigin
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageForwardOrigin] -> ShowS
$cshowList :: [MessageForwardOrigin] -> ShowS
show :: MessageForwardOrigin -> String
$cshow :: MessageForwardOrigin -> String
showsPrec :: I32 -> MessageForwardOrigin -> ShowS
$cshowsPrec :: I32 -> MessageForwardOrigin -> ShowS
Show, MessageForwardOrigin -> MessageForwardOrigin -> Bool
(MessageForwardOrigin -> MessageForwardOrigin -> Bool)
-> (MessageForwardOrigin -> MessageForwardOrigin -> Bool)
-> Eq MessageForwardOrigin
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageForwardOrigin -> MessageForwardOrigin -> Bool
$c/= :: MessageForwardOrigin -> MessageForwardOrigin -> Bool
== :: MessageForwardOrigin -> MessageForwardOrigin -> Bool
$c== :: MessageForwardOrigin -> MessageForwardOrigin -> Bool
Eq, (forall x. MessageForwardOrigin -> Rep MessageForwardOrigin x)
-> (forall x. Rep MessageForwardOrigin x -> MessageForwardOrigin)
-> Generic MessageForwardOrigin
forall x. Rep MessageForwardOrigin x -> MessageForwardOrigin
forall x. MessageForwardOrigin -> Rep MessageForwardOrigin x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageForwardOrigin x -> MessageForwardOrigin
$cfrom :: forall x. MessageForwardOrigin -> Rep MessageForwardOrigin x
Generic)
data MessageForwardInfo
  = -- | Contains information about a forwarded message
  MessageForwardInfo
    { -- | Origin of a forwarded message
      MessageForwardInfo -> MessageForwardOrigin
origin_1 :: MessageForwardOrigin,
      -- | Point in time (Unix timestamp) when the message was originally sent
      MessageForwardInfo -> I32
date_1 :: I32,
      -- | The type of a public service announcement for the forwarded message
      MessageForwardInfo -> T
public_service_announcement_type_1 :: T,
      -- | For messages forwarded to the chat with the current user (Saved Messages) or to the channel's discussion group, the identifier of the chat from which the message was forwarded last time; 0 if unknown
      MessageForwardInfo -> I32
from_chat_id_1 :: I53,
      -- | For messages forwarded to the chat with the current user (Saved Messages) or to the channel's discussion group, the identifier of the original message from which the new message was forwarded last time; 0 if unknown
      MessageForwardInfo -> I32
from_message_id_1 :: I53
    }
  deriving (I32 -> MessageForwardInfo -> ShowS
[MessageForwardInfo] -> ShowS
MessageForwardInfo -> String
(I32 -> MessageForwardInfo -> ShowS)
-> (MessageForwardInfo -> String)
-> ([MessageForwardInfo] -> ShowS)
-> Show MessageForwardInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageForwardInfo] -> ShowS
$cshowList :: [MessageForwardInfo] -> ShowS
show :: MessageForwardInfo -> String
$cshow :: MessageForwardInfo -> String
showsPrec :: I32 -> MessageForwardInfo -> ShowS
$cshowsPrec :: I32 -> MessageForwardInfo -> ShowS
Show, MessageForwardInfo -> MessageForwardInfo -> Bool
(MessageForwardInfo -> MessageForwardInfo -> Bool)
-> (MessageForwardInfo -> MessageForwardInfo -> Bool)
-> Eq MessageForwardInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageForwardInfo -> MessageForwardInfo -> Bool
$c/= :: MessageForwardInfo -> MessageForwardInfo -> Bool
== :: MessageForwardInfo -> MessageForwardInfo -> Bool
$c== :: MessageForwardInfo -> MessageForwardInfo -> Bool
Eq, (forall x. MessageForwardInfo -> Rep MessageForwardInfo x)
-> (forall x. Rep MessageForwardInfo x -> MessageForwardInfo)
-> Generic MessageForwardInfo
forall x. Rep MessageForwardInfo x -> MessageForwardInfo
forall x. MessageForwardInfo -> Rep MessageForwardInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageForwardInfo x -> MessageForwardInfo
$cfrom :: forall x. MessageForwardInfo -> Rep MessageForwardInfo x
Generic)
-- | Contains information about the sending state of the message
data MessageSendingState
  = -- | The message is being sent now, but has not yet been delivered to the server
  MessageSendingStatePending
    { 
    }
  | -- | The message failed to be sent 
  MessageSendingStateFailed
    { -- | An error code; 0 if unknown 
      MessageSendingState -> I32
error_code_2 :: I32,
      -- | Error message
      MessageSendingState -> T
error_message_2 :: T,
      -- | True, if the message can be re-sent 
      MessageSendingState -> Bool
can_retry_2 :: Bool,
      -- | Time left before the message can be re-sent, in seconds. No update is sent when this field changes
      MessageSendingState -> Double
retry_after_2 :: Double
    }
  deriving (I32 -> MessageSendingState -> ShowS
[MessageSendingState] -> ShowS
MessageSendingState -> String
(I32 -> MessageSendingState -> ShowS)
-> (MessageSendingState -> String)
-> ([MessageSendingState] -> ShowS)
-> Show MessageSendingState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageSendingState] -> ShowS
$cshowList :: [MessageSendingState] -> ShowS
show :: MessageSendingState -> String
$cshow :: MessageSendingState -> String
showsPrec :: I32 -> MessageSendingState -> ShowS
$cshowsPrec :: I32 -> MessageSendingState -> ShowS
Show, MessageSendingState -> MessageSendingState -> Bool
(MessageSendingState -> MessageSendingState -> Bool)
-> (MessageSendingState -> MessageSendingState -> Bool)
-> Eq MessageSendingState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageSendingState -> MessageSendingState -> Bool
$c/= :: MessageSendingState -> MessageSendingState -> Bool
== :: MessageSendingState -> MessageSendingState -> Bool
$c== :: MessageSendingState -> MessageSendingState -> Bool
Eq, (forall x. MessageSendingState -> Rep MessageSendingState x)
-> (forall x. Rep MessageSendingState x -> MessageSendingState)
-> Generic MessageSendingState
forall x. Rep MessageSendingState x -> MessageSendingState
forall x. MessageSendingState -> Rep MessageSendingState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageSendingState x -> MessageSendingState
$cfrom :: forall x. MessageSendingState -> Rep MessageSendingState x
Generic)
data Message
  = -- | Describes a message
  Message
    { -- | Message identifier, unique for the chat to which the message belongs
      Message -> I32
id_1 :: I53,
      -- | Identifier of the user who sent the message; 0 if unknown. Currently, it is unknown for channel posts and for channel posts automatically forwarded to discussion group
      Message -> I32
sender_user_id_1 :: I32,
      -- | Chat identifier
      Message -> I32
chat_id_1 :: I53,
      -- | Information about the sending state of the message; may be null
      Message -> MessageSendingState
sending_state_1 :: MessageSendingState,
      -- | Information about the scheduling state of the message; may be null
      Message -> MessageSchedulingState
scheduling_state_1 :: MessageSchedulingState,
      -- | True, if the message is outgoing
      Message -> Bool
is_outgoing_1 :: Bool,
      -- | True, if the message can be edited. For live location and poll messages this fields shows whether editMessageLiveLocation or stopPoll can be used with this message by the client
      Message -> Bool
can_be_edited_1 :: Bool,
      -- | True, if the message can be forwarded
      Message -> Bool
can_be_forwarded_1 :: Bool,
      -- | True, if the message can be deleted only for the current user while other users will continue to see it
      Message -> Bool
can_be_deleted_only_for_self_1 :: Bool,
      -- | True, if the message can be deleted for all users
      Message -> Bool
can_be_deleted_for_all_users_1 :: Bool,
      -- | True, if the message is a channel post. All messages to channels are channel posts, all other messages are not channel posts
      Message -> Bool
is_channel_post_1 :: Bool,
      -- | True, if the message contains an unread mention for the current user
      Message -> Bool
contains_unread_mention_1 :: Bool,
      -- | Point in time (Unix timestamp) when the message was sent
      Message -> I32
date_1 :: I32,
      -- | Point in time (Unix timestamp) when the message was last edited
      Message -> I32
edit_date_1 :: I32,
      -- | Information about the initial message sender; may be null
      Message -> MessageForwardInfo
forward_info_1 :: MessageForwardInfo,
      -- | If non-zero, the identifier of the message this message is replying to; can be the identifier of a deleted message
      Message -> I32
reply_to_message_id_1 :: I53,
      -- | For self-destructing messages, the message's TTL (Time To Live), in seconds; 0 if none. TDLib will send updateDeleteMessages or updateMessageContent once the TTL expires
      Message -> I32
ttl_1 :: I32,
      -- | Time left before the message expires, in seconds
      Message -> Double
ttl_expires_in_1 :: Double,
      -- | If non-zero, the user identifier of the bot through which this message was sent
      Message -> I32
via_bot_user_id_1 :: I32,
      -- | For channel posts, optional author signature
      Message -> T
author_signature_1 :: T,
      -- | Number of times this message was viewed
      Message -> I32
views_1 :: I32,
      -- | Unique identifier of an album this message belongs to. Only photos and videos can be grouped together in albums
      Message -> I64
media_album_id_1 :: I64,
      -- | If non-empty, contains a human-readable description of the reason why access to this message must be restricted
      Message -> T
restriction_reason_1 :: T,
      -- | Content of the message
      Message -> MessageContent
content_1 :: MessageContent,
      -- | Reply markup for the message; may be null
      Message -> ReplyMarkup
reply_markup_1 :: ReplyMarkup
    }
  deriving (I32 -> Message -> ShowS
[Message] -> ShowS
Message -> String
(I32 -> Message -> ShowS)
-> (Message -> String) -> ([Message] -> ShowS) -> Show Message
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Message] -> ShowS
$cshowList :: [Message] -> ShowS
show :: Message -> String
$cshow :: Message -> String
showsPrec :: I32 -> Message -> ShowS
$cshowsPrec :: I32 -> Message -> ShowS
Show, Message -> Message -> Bool
(Message -> Message -> Bool)
-> (Message -> Message -> Bool) -> Eq Message
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Message -> Message -> Bool
$c/= :: Message -> Message -> Bool
== :: Message -> Message -> Bool
$c== :: Message -> Message -> Bool
Eq, (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)
data Messages
  = -- | Contains a list of messages 
  Messages
    { -- | Approximate total count of messages found 
      Messages -> I32
total_count_1 :: I32,
      -- | List of messages; messages may be null
      Messages -> [Message]
messages_1 :: ([]) (Message)
    }
  deriving (I32 -> Messages -> ShowS
[Messages] -> ShowS
Messages -> String
(I32 -> Messages -> ShowS)
-> (Messages -> String) -> ([Messages] -> ShowS) -> Show Messages
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Messages] -> ShowS
$cshowList :: [Messages] -> ShowS
show :: Messages -> String
$cshow :: Messages -> String
showsPrec :: I32 -> Messages -> ShowS
$cshowsPrec :: I32 -> Messages -> ShowS
Show, Messages -> Messages -> Bool
(Messages -> Messages -> Bool)
-> (Messages -> Messages -> Bool) -> Eq Messages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Messages -> Messages -> Bool
$c/= :: Messages -> Messages -> Bool
== :: Messages -> Messages -> Bool
$c== :: Messages -> Messages -> Bool
Eq, (forall x. Messages -> Rep Messages x)
-> (forall x. Rep Messages x -> Messages) -> Generic Messages
forall x. Rep Messages x -> Messages
forall x. Messages -> Rep Messages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Messages x -> Messages
$cfrom :: forall x. Messages -> Rep Messages x
Generic)
data FoundMessages
  = -- | Contains a list of messages found by a search 
  FoundMessages
    { -- | List of messages 
      FoundMessages -> [Message]
messages_1 :: ([]) (Message),
      -- | Value to pass as from_search_id to get more results
      FoundMessages -> I64
next_from_search_id_1 :: I64
    }
  deriving (I32 -> FoundMessages -> ShowS
[FoundMessages] -> ShowS
FoundMessages -> String
(I32 -> FoundMessages -> ShowS)
-> (FoundMessages -> String)
-> ([FoundMessages] -> ShowS)
-> Show FoundMessages
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FoundMessages] -> ShowS
$cshowList :: [FoundMessages] -> ShowS
show :: FoundMessages -> String
$cshow :: FoundMessages -> String
showsPrec :: I32 -> FoundMessages -> ShowS
$cshowsPrec :: I32 -> FoundMessages -> ShowS
Show, FoundMessages -> FoundMessages -> Bool
(FoundMessages -> FoundMessages -> Bool)
-> (FoundMessages -> FoundMessages -> Bool) -> Eq FoundMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FoundMessages -> FoundMessages -> Bool
$c/= :: FoundMessages -> FoundMessages -> Bool
== :: FoundMessages -> FoundMessages -> Bool
$c== :: FoundMessages -> FoundMessages -> Bool
Eq, (forall x. FoundMessages -> Rep FoundMessages x)
-> (forall x. Rep FoundMessages x -> FoundMessages)
-> Generic FoundMessages
forall x. Rep FoundMessages x -> FoundMessages
forall x. FoundMessages -> Rep FoundMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FoundMessages x -> FoundMessages
$cfrom :: forall x. FoundMessages -> Rep FoundMessages x
Generic)
-- | Describes the types of chats to which notification settings are applied
data NotificationSettingsScope
  = -- | Notification settings applied to all private and secret chats when the corresponding chat setting has a default value
  NotificationSettingsScopePrivateChats
    { 
    }
  | -- | Notification settings applied to all basic groups and supergroups when the corresponding chat setting has a default value
  NotificationSettingsScopeGroupChats
    { 
    }
  | -- | Notification settings applied to all channels when the corresponding chat setting has a default value
  NotificationSettingsScopeChannelChats
    { 
    }
  deriving (I32 -> NotificationSettingsScope -> ShowS
[NotificationSettingsScope] -> ShowS
NotificationSettingsScope -> String
(I32 -> NotificationSettingsScope -> ShowS)
-> (NotificationSettingsScope -> String)
-> ([NotificationSettingsScope] -> ShowS)
-> Show NotificationSettingsScope
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationSettingsScope] -> ShowS
$cshowList :: [NotificationSettingsScope] -> ShowS
show :: NotificationSettingsScope -> String
$cshow :: NotificationSettingsScope -> String
showsPrec :: I32 -> NotificationSettingsScope -> ShowS
$cshowsPrec :: I32 -> NotificationSettingsScope -> ShowS
Show, NotificationSettingsScope -> NotificationSettingsScope -> Bool
(NotificationSettingsScope -> NotificationSettingsScope -> Bool)
-> (NotificationSettingsScope -> NotificationSettingsScope -> Bool)
-> Eq NotificationSettingsScope
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationSettingsScope -> NotificationSettingsScope -> Bool
$c/= :: NotificationSettingsScope -> NotificationSettingsScope -> Bool
== :: NotificationSettingsScope -> NotificationSettingsScope -> Bool
$c== :: NotificationSettingsScope -> NotificationSettingsScope -> Bool
Eq, (forall x.
 NotificationSettingsScope -> Rep NotificationSettingsScope x)
-> (forall x.
    Rep NotificationSettingsScope x -> NotificationSettingsScope)
-> Generic NotificationSettingsScope
forall x.
Rep NotificationSettingsScope x -> NotificationSettingsScope
forall x.
NotificationSettingsScope -> Rep NotificationSettingsScope x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep NotificationSettingsScope x -> NotificationSettingsScope
$cfrom :: forall x.
NotificationSettingsScope -> Rep NotificationSettingsScope x
Generic)
data ChatNotificationSettings
  = -- | Contains information about notification settings for a chat
  ChatNotificationSettings
    { -- | If true, mute_for is ignored and the value for the relevant type of chat is used instead 
      ChatNotificationSettings -> Bool
use_default_mute_for_1 :: Bool,
      -- | Time left before notifications will be unmuted, in seconds
      ChatNotificationSettings -> I32
mute_for_1 :: I32,
      -- | If true, sound is ignored and the value for the relevant type of chat is used instead 
      ChatNotificationSettings -> Bool
use_default_sound_1 :: Bool,
      -- | The name of an audio file to be used for notification sounds; only applies to iOS applications
      ChatNotificationSettings -> T
sound_1 :: T,
      -- | If true, show_preview is ignored and the value for the relevant type of chat is used instead 
      ChatNotificationSettings -> Bool
use_default_show_preview_1 :: Bool,
      -- | True, if message content should be displayed in notifications
      ChatNotificationSettings -> Bool
show_preview_1 :: Bool,
      -- | If true, disable_pinned_message_notifications is ignored and the value for the relevant type of chat is used instead 
      ChatNotificationSettings -> Bool
use_default_disable_pinned_message_notifications_1 :: Bool,
      -- | If true, notifications for incoming pinned messages will be created as for an ordinary unread message
      ChatNotificationSettings -> Bool
disable_pinned_message_notifications_1 :: Bool,
      -- | If true, disable_mention_notifications is ignored and the value for the relevant type of chat is used instead 
      ChatNotificationSettings -> Bool
use_default_disable_mention_notifications_1 :: Bool,
      -- | If true, notifications for messages with mentions will be created as for an ordinary unread message
      ChatNotificationSettings -> Bool
disable_mention_notifications_1 :: Bool
    }
  deriving (I32 -> ChatNotificationSettings -> ShowS
[ChatNotificationSettings] -> ShowS
ChatNotificationSettings -> String
(I32 -> ChatNotificationSettings -> ShowS)
-> (ChatNotificationSettings -> String)
-> ([ChatNotificationSettings] -> ShowS)
-> Show ChatNotificationSettings
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatNotificationSettings] -> ShowS
$cshowList :: [ChatNotificationSettings] -> ShowS
show :: ChatNotificationSettings -> String
$cshow :: ChatNotificationSettings -> String
showsPrec :: I32 -> ChatNotificationSettings -> ShowS
$cshowsPrec :: I32 -> ChatNotificationSettings -> ShowS
Show, ChatNotificationSettings -> ChatNotificationSettings -> Bool
(ChatNotificationSettings -> ChatNotificationSettings -> Bool)
-> (ChatNotificationSettings -> ChatNotificationSettings -> Bool)
-> Eq ChatNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatNotificationSettings -> ChatNotificationSettings -> Bool
$c/= :: ChatNotificationSettings -> ChatNotificationSettings -> Bool
== :: ChatNotificationSettings -> ChatNotificationSettings -> Bool
$c== :: ChatNotificationSettings -> ChatNotificationSettings -> Bool
Eq, (forall x.
 ChatNotificationSettings -> Rep ChatNotificationSettings x)
-> (forall x.
    Rep ChatNotificationSettings x -> ChatNotificationSettings)
-> Generic ChatNotificationSettings
forall x.
Rep ChatNotificationSettings x -> ChatNotificationSettings
forall x.
ChatNotificationSettings -> Rep ChatNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ChatNotificationSettings x -> ChatNotificationSettings
$cfrom :: forall x.
ChatNotificationSettings -> Rep ChatNotificationSettings x
Generic)
data ScopeNotificationSettings
  = -- | Contains information about notification settings for several chats
  ScopeNotificationSettings
    { -- | Time left before notifications will be unmuted, in seconds
      ScopeNotificationSettings -> I32
mute_for_1 :: I32,
      -- | The name of an audio file to be used for notification sounds; only applies to iOS applications
      ScopeNotificationSettings -> T
sound_1 :: T,
      -- | True, if message content should be displayed in notifications
      ScopeNotificationSettings -> Bool
show_preview_1 :: Bool,
      -- | True, if notifications for incoming pinned messages will be created as for an ordinary unread message
      ScopeNotificationSettings -> Bool
disable_pinned_message_notifications_1 :: Bool,
      -- | True, if notifications for messages with mentions will be created as for an ordinary unread message
      ScopeNotificationSettings -> Bool
disable_mention_notifications_1 :: Bool
    }
  deriving (I32 -> ScopeNotificationSettings -> ShowS
[ScopeNotificationSettings] -> ShowS
ScopeNotificationSettings -> String
(I32 -> ScopeNotificationSettings -> ShowS)
-> (ScopeNotificationSettings -> String)
-> ([ScopeNotificationSettings] -> ShowS)
-> Show ScopeNotificationSettings
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScopeNotificationSettings] -> ShowS
$cshowList :: [ScopeNotificationSettings] -> ShowS
show :: ScopeNotificationSettings -> String
$cshow :: ScopeNotificationSettings -> String
showsPrec :: I32 -> ScopeNotificationSettings -> ShowS
$cshowsPrec :: I32 -> ScopeNotificationSettings -> ShowS
Show, ScopeNotificationSettings -> ScopeNotificationSettings -> Bool
(ScopeNotificationSettings -> ScopeNotificationSettings -> Bool)
-> (ScopeNotificationSettings -> ScopeNotificationSettings -> Bool)
-> Eq ScopeNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScopeNotificationSettings -> ScopeNotificationSettings -> Bool
$c/= :: ScopeNotificationSettings -> ScopeNotificationSettings -> Bool
== :: ScopeNotificationSettings -> ScopeNotificationSettings -> Bool
$c== :: ScopeNotificationSettings -> ScopeNotificationSettings -> Bool
Eq, (forall x.
 ScopeNotificationSettings -> Rep ScopeNotificationSettings x)
-> (forall x.
    Rep ScopeNotificationSettings x -> ScopeNotificationSettings)
-> Generic ScopeNotificationSettings
forall x.
Rep ScopeNotificationSettings x -> ScopeNotificationSettings
forall x.
ScopeNotificationSettings -> Rep ScopeNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ScopeNotificationSettings x -> ScopeNotificationSettings
$cfrom :: forall x.
ScopeNotificationSettings -> Rep ScopeNotificationSettings x
Generic)
data DraftMessage
  = -- | Contains information about a message draft
  DraftMessage
    { -- | Identifier of the message to reply to; 0 if none
      DraftMessage -> I32
reply_to_message_id_1 :: I53,
      -- | Point in time (Unix timestamp) when the draft was created
      DraftMessage -> I32
date_1 :: I32,
      -- | Content of the message draft; this should always be of type inputMessageText
      DraftMessage -> InputMessageContent
input_message_text_1 :: InputMessageContent
    }
  deriving (I32 -> DraftMessage -> ShowS
[DraftMessage] -> ShowS
DraftMessage -> String
(I32 -> DraftMessage -> ShowS)
-> (DraftMessage -> String)
-> ([DraftMessage] -> ShowS)
-> Show DraftMessage
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DraftMessage] -> ShowS
$cshowList :: [DraftMessage] -> ShowS
show :: DraftMessage -> String
$cshow :: DraftMessage -> String
showsPrec :: I32 -> DraftMessage -> ShowS
$cshowsPrec :: I32 -> DraftMessage -> ShowS
Show, DraftMessage -> DraftMessage -> Bool
(DraftMessage -> DraftMessage -> Bool)
-> (DraftMessage -> DraftMessage -> Bool) -> Eq DraftMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DraftMessage -> DraftMessage -> Bool
$c/= :: DraftMessage -> DraftMessage -> Bool
== :: DraftMessage -> DraftMessage -> Bool
$c== :: DraftMessage -> DraftMessage -> Bool
Eq, (forall x. DraftMessage -> Rep DraftMessage x)
-> (forall x. Rep DraftMessage x -> DraftMessage)
-> Generic DraftMessage
forall x. Rep DraftMessage x -> DraftMessage
forall x. DraftMessage -> Rep DraftMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DraftMessage x -> DraftMessage
$cfrom :: forall x. DraftMessage -> Rep DraftMessage x
Generic)
-- | Describes the type of a chat
data ChatType
  = -- | An ordinary chat with a user 
  ChatTypePrivate
    { -- | User identifier
      ChatType -> I32
user_id_1 :: I32
    }
  | -- | A basic group (i.e., a chat with 0-200 other users) 
  ChatTypeBasicGroup
    { -- | Basic group identifier
      ChatType -> I32
basic_group_id_2 :: I32
    }
  | -- | A supergroup (i.e. a chat with up to GetOption("supergroup_max_size") other users), or channel (with unlimited members) 
  ChatTypeSupergroup
    { -- | Supergroup or channel identifier 
      ChatType -> I32
supergroup_id_3 :: I32,
      -- | True, if the supergroup is a channel
      ChatType -> Bool
is_channel_3 :: Bool
    }
  | -- | A secret chat with a user 
  ChatTypeSecret
    { -- | Secret chat identifier 
      ChatType -> I32
secret_chat_id_4 :: I32,
      -- | User identifier of the secret chat peer
      ChatType -> I32
user_id_4 :: I32
    }
  deriving (I32 -> ChatType -> ShowS
[ChatType] -> ShowS
ChatType -> String
(I32 -> ChatType -> ShowS)
-> (ChatType -> String) -> ([ChatType] -> ShowS) -> Show ChatType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatType] -> ShowS
$cshowList :: [ChatType] -> ShowS
show :: ChatType -> String
$cshow :: ChatType -> String
showsPrec :: I32 -> ChatType -> ShowS
$cshowsPrec :: I32 -> ChatType -> ShowS
Show, ChatType -> ChatType -> Bool
(ChatType -> ChatType -> Bool)
-> (ChatType -> ChatType -> Bool) -> Eq ChatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatType -> ChatType -> Bool
$c/= :: ChatType -> ChatType -> Bool
== :: ChatType -> ChatType -> Bool
$c== :: ChatType -> ChatType -> Bool
Eq, (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)
-- | Describes a list of chats
data ChatList
  = -- | A main list of chats
  ChatListMain
    { 
    }
  | -- | A list of chats usually located at the top of the main chat list. Unmuted chats are automatically moved from the Archive to the Main chat list when a new message arrives
  ChatListArchive
    { 
    }
  deriving (I32 -> ChatList -> ShowS
[ChatList] -> ShowS
ChatList -> String
(I32 -> ChatList -> ShowS)
-> (ChatList -> String) -> ([ChatList] -> ShowS) -> Show ChatList
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatList] -> ShowS
$cshowList :: [ChatList] -> ShowS
show :: ChatList -> String
$cshow :: ChatList -> String
showsPrec :: I32 -> ChatList -> ShowS
$cshowsPrec :: I32 -> ChatList -> ShowS
Show, ChatList -> ChatList -> Bool
(ChatList -> ChatList -> Bool)
-> (ChatList -> ChatList -> Bool) -> Eq ChatList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatList -> ChatList -> Bool
$c/= :: ChatList -> ChatList -> Bool
== :: ChatList -> ChatList -> Bool
$c== :: ChatList -> ChatList -> Bool
Eq, (forall x. ChatList -> Rep ChatList x)
-> (forall x. Rep ChatList x -> ChatList) -> Generic ChatList
forall x. Rep ChatList x -> ChatList
forall x. ChatList -> Rep ChatList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatList x -> ChatList
$cfrom :: forall x. ChatList -> Rep ChatList x
Generic)
-- | Describes a reason why the chat is shown in a chat list
data ChatSource
  = -- | The chat is sponsored by the user's MTProxy server
  ChatSourceMtprotoProxy
    { 
    }
  | -- | The chat contains a public service announcement 
  ChatSourcePublicServiceAnnouncement
    { -- | The type of the announcement 
      ChatSource -> T
type_2 :: T,
      -- | The text of the announcement
      ChatSource -> T
text_2 :: T
    }
  deriving (I32 -> ChatSource -> ShowS
[ChatSource] -> ShowS
ChatSource -> String
(I32 -> ChatSource -> ShowS)
-> (ChatSource -> String)
-> ([ChatSource] -> ShowS)
-> Show ChatSource
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatSource] -> ShowS
$cshowList :: [ChatSource] -> ShowS
show :: ChatSource -> String
$cshow :: ChatSource -> String
showsPrec :: I32 -> ChatSource -> ShowS
$cshowsPrec :: I32 -> ChatSource -> ShowS
Show, ChatSource -> ChatSource -> Bool
(ChatSource -> ChatSource -> Bool)
-> (ChatSource -> ChatSource -> Bool) -> Eq ChatSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatSource -> ChatSource -> Bool
$c/= :: ChatSource -> ChatSource -> Bool
== :: ChatSource -> ChatSource -> Bool
$c== :: ChatSource -> ChatSource -> Bool
Eq, (forall x. ChatSource -> Rep ChatSource x)
-> (forall x. Rep ChatSource x -> ChatSource) -> Generic ChatSource
forall x. Rep ChatSource x -> ChatSource
forall x. ChatSource -> Rep ChatSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatSource x -> ChatSource
$cfrom :: forall x. ChatSource -> Rep ChatSource x
Generic)
data Chat
  = -- | A chat. (Can be a private chat, basic group, supergroup, or secret chat)
  Chat
    { -- | Chat unique identifier
      Chat -> I32
id_1 :: I53,
      -- | Type of the chat
      Chat -> ChatType
type_1 :: ChatType,
      -- | A chat list to which the chat belongs; may be null
      Chat -> ChatList
chat_list_1 :: ChatList,
      -- | Chat title
      Chat -> T
title_1 :: T,
      -- | Chat photo; may be null
      Chat -> ChatPhoto
photo_1 :: ChatPhoto,
      -- | Actions that non-administrator chat members are allowed to take in the chat
      Chat -> ChatPermissions
permissions_1 :: ChatPermissions,
      -- | Last message in the chat; may be null
      Chat -> Message
last_message_1 :: Message,
      -- | Descending parameter by which chats are sorted in the main chat list. If the order number of two chats is the same, they must be sorted in descending order by ID. If 0, the position of the chat in the list is undetermined
      Chat -> I64
order_1 :: I64,
      -- | Source of the chat in a chat list; may be null
      Chat -> ChatSource
source_1 :: ChatSource,
      -- | True, if the chat is pinned
      Chat -> Bool
is_pinned_1 :: Bool,
      -- | True, if the chat is marked as unread
      Chat -> Bool
is_marked_as_unread_1 :: Bool,
      -- | True, if the chat has scheduled messages
      Chat -> Bool
has_scheduled_messages_1 :: Bool,
      -- | True, if the chat messages can be deleted only for the current user while other users will continue to see the messages
      Chat -> Bool
can_be_deleted_only_for_self_1 :: Bool,
      -- | True, if the chat messages can be deleted for all users
      Chat -> Bool
can_be_deleted_for_all_users_1 :: Bool,
      -- | True, if the chat can be reported to Telegram moderators through reportChat
      Chat -> Bool
can_be_reported_1 :: Bool,
      -- | Default value of the disable_notification parameter, used when a message is sent to the chat
      Chat -> Bool
default_disable_notification_1 :: Bool,
      -- | Number of unread messages in the chat
      Chat -> I32
unread_count_1 :: I32,
      -- | Identifier of the last read incoming message
      Chat -> I32
last_read_inbox_message_id_1 :: I53,
      -- | Identifier of the last read outgoing message
      Chat -> I32
last_read_outbox_message_id_1 :: I53,
      -- | Number of unread messages with a mention/reply in the chat
      Chat -> I32
unread_mention_count_1 :: I32,
      -- | Notification settings for this chat
      Chat -> ChatNotificationSettings
notification_settings_1 :: ChatNotificationSettings,
      -- | Describes actions which should be possible to do through a chat action bar; may be null
      Chat -> ChatActionBar
action_bar_1 :: ChatActionBar,
      -- | Identifier of the pinned message in the chat; 0 if none
      Chat -> I32
pinned_message_id_1 :: I53,
      -- | Identifier of the message from which reply markup needs to be used; 0 if there is no default custom reply markup in the chat
      Chat -> I32
reply_markup_message_id_1 :: I53,
      -- | A draft of a message in the chat; may be null
      Chat -> DraftMessage
draft_message_1 :: DraftMessage,
      -- | Contains client-specific data associated with the chat. (For example, the chat position or local chat notification settings can be stored here.) Persistent if the message database is used
      Chat -> T
client_data_1 :: T
    }
  deriving (I32 -> Chat -> ShowS
[Chat] -> ShowS
Chat -> String
(I32 -> Chat -> ShowS)
-> (Chat -> String) -> ([Chat] -> ShowS) -> Show Chat
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chat] -> ShowS
$cshowList :: [Chat] -> ShowS
show :: Chat -> String
$cshow :: Chat -> String
showsPrec :: I32 -> Chat -> ShowS
$cshowsPrec :: I32 -> Chat -> ShowS
Show, Chat -> Chat -> Bool
(Chat -> Chat -> Bool) -> (Chat -> Chat -> Bool) -> Eq Chat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chat -> Chat -> Bool
$c/= :: Chat -> Chat -> Bool
== :: Chat -> Chat -> Bool
$c== :: Chat -> Chat -> Bool
Eq, (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)
data Chats
  = -- | Represents a list of chats 
  Chats
    { -- | List of chat identifiers
      Chats -> [I32]
chat_ids_1 :: ([]) (I53)
    }
  deriving (I32 -> Chats -> ShowS
[Chats] -> ShowS
Chats -> String
(I32 -> Chats -> ShowS)
-> (Chats -> String) -> ([Chats] -> ShowS) -> Show Chats
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Chats] -> ShowS
$cshowList :: [Chats] -> ShowS
show :: Chats -> String
$cshow :: Chats -> String
showsPrec :: I32 -> Chats -> ShowS
$cshowsPrec :: I32 -> Chats -> ShowS
Show, Chats -> Chats -> Bool
(Chats -> Chats -> Bool) -> (Chats -> Chats -> Bool) -> Eq Chats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Chats -> Chats -> Bool
$c/= :: Chats -> Chats -> Bool
== :: Chats -> Chats -> Bool
$c== :: Chats -> Chats -> Bool
Eq, (forall x. Chats -> Rep Chats x)
-> (forall x. Rep Chats x -> Chats) -> Generic Chats
forall x. Rep Chats x -> Chats
forall x. Chats -> Rep Chats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Chats x -> Chats
$cfrom :: forall x. Chats -> Rep Chats x
Generic)
data ChatNearby
  = -- | Describes a chat located nearby 
  ChatNearby
    { -- | Chat identifier 
      ChatNearby -> I32
chat_id_1 :: I53,
      -- | Distance to the chat location in meters
      ChatNearby -> I32
distance_1 :: I32
    }
  deriving (I32 -> ChatNearby -> ShowS
[ChatNearby] -> ShowS
ChatNearby -> String
(I32 -> ChatNearby -> ShowS)
-> (ChatNearby -> String)
-> ([ChatNearby] -> ShowS)
-> Show ChatNearby
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatNearby] -> ShowS
$cshowList :: [ChatNearby] -> ShowS
show :: ChatNearby -> String
$cshow :: ChatNearby -> String
showsPrec :: I32 -> ChatNearby -> ShowS
$cshowsPrec :: I32 -> ChatNearby -> ShowS
Show, ChatNearby -> ChatNearby -> Bool
(ChatNearby -> ChatNearby -> Bool)
-> (ChatNearby -> ChatNearby -> Bool) -> Eq ChatNearby
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatNearby -> ChatNearby -> Bool
$c/= :: ChatNearby -> ChatNearby -> Bool
== :: ChatNearby -> ChatNearby -> Bool
$c== :: ChatNearby -> ChatNearby -> Bool
Eq, (forall x. ChatNearby -> Rep ChatNearby x)
-> (forall x. Rep ChatNearby x -> ChatNearby) -> Generic ChatNearby
forall x. Rep ChatNearby x -> ChatNearby
forall x. ChatNearby -> Rep ChatNearby x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatNearby x -> ChatNearby
$cfrom :: forall x. ChatNearby -> Rep ChatNearby x
Generic)
data ChatsNearby
  = -- | Represents a list of chats located nearby 
  ChatsNearby
    { -- | List of users nearby 
      ChatsNearby -> [ChatNearby]
users_nearby_1 :: ([]) (ChatNearby),
      -- | List of location-based supergroups nearby
      ChatsNearby -> [ChatNearby]
supergroups_nearby_1 :: ([]) (ChatNearby)
    }
  deriving (I32 -> ChatsNearby -> ShowS
[ChatsNearby] -> ShowS
ChatsNearby -> String
(I32 -> ChatsNearby -> ShowS)
-> (ChatsNearby -> String)
-> ([ChatsNearby] -> ShowS)
-> Show ChatsNearby
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatsNearby] -> ShowS
$cshowList :: [ChatsNearby] -> ShowS
show :: ChatsNearby -> String
$cshow :: ChatsNearby -> String
showsPrec :: I32 -> ChatsNearby -> ShowS
$cshowsPrec :: I32 -> ChatsNearby -> ShowS
Show, ChatsNearby -> ChatsNearby -> Bool
(ChatsNearby -> ChatsNearby -> Bool)
-> (ChatsNearby -> ChatsNearby -> Bool) -> Eq ChatsNearby
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatsNearby -> ChatsNearby -> Bool
$c/= :: ChatsNearby -> ChatsNearby -> Bool
== :: ChatsNearby -> ChatsNearby -> Bool
$c== :: ChatsNearby -> ChatsNearby -> Bool
Eq, (forall x. ChatsNearby -> Rep ChatsNearby x)
-> (forall x. Rep ChatsNearby x -> ChatsNearby)
-> Generic ChatsNearby
forall x. Rep ChatsNearby x -> ChatsNearby
forall x. ChatsNearby -> Rep ChatsNearby x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatsNearby x -> ChatsNearby
$cfrom :: forall x. ChatsNearby -> Rep ChatsNearby x
Generic)
data ChatInviteLink
  = -- | Contains a chat invite link 
  ChatInviteLink
    { -- | Chat invite link
      ChatInviteLink -> T
invite_link_1 :: T
    }
  deriving (I32 -> ChatInviteLink -> ShowS
[ChatInviteLink] -> ShowS
ChatInviteLink -> String
(I32 -> ChatInviteLink -> ShowS)
-> (ChatInviteLink -> String)
-> ([ChatInviteLink] -> ShowS)
-> Show ChatInviteLink
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatInviteLink] -> ShowS
$cshowList :: [ChatInviteLink] -> ShowS
show :: ChatInviteLink -> String
$cshow :: ChatInviteLink -> String
showsPrec :: I32 -> ChatInviteLink -> ShowS
$cshowsPrec :: I32 -> ChatInviteLink -> ShowS
Show, ChatInviteLink -> ChatInviteLink -> Bool
(ChatInviteLink -> ChatInviteLink -> Bool)
-> (ChatInviteLink -> ChatInviteLink -> Bool) -> Eq ChatInviteLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatInviteLink -> ChatInviteLink -> Bool
$c/= :: ChatInviteLink -> ChatInviteLink -> Bool
== :: ChatInviteLink -> ChatInviteLink -> Bool
$c== :: ChatInviteLink -> ChatInviteLink -> Bool
Eq, (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)
data ChatInviteLinkInfo
  = -- | Contains information about a chat invite link
  ChatInviteLinkInfo
    { -- | Chat identifier of the invite link; 0 if the user is not a member of this chat
      ChatInviteLinkInfo -> I32
chat_id_1 :: I53,
      -- | Contains information about the type of the chat
      ChatInviteLinkInfo -> ChatType
type_1 :: ChatType,
      -- | Title of the chat
      ChatInviteLinkInfo -> T
title_1 :: T,
      -- | Chat photo; may be null
      ChatInviteLinkInfo -> ChatPhoto
photo_1 :: ChatPhoto,
      -- | Number of members in the chat
      ChatInviteLinkInfo -> I32
member_count_1 :: I32,
      -- | User identifiers of some chat members that may be known to the current user
      ChatInviteLinkInfo -> [I32]
member_user_ids_1 :: ([]) (I32),
      -- | True, if the chat is a public supergroup or channel, i.e. it has a username or it is a location-based supergroup
      ChatInviteLinkInfo -> Bool
is_public_1 :: Bool
    }
  deriving (I32 -> ChatInviteLinkInfo -> ShowS
[ChatInviteLinkInfo] -> ShowS
ChatInviteLinkInfo -> String
(I32 -> ChatInviteLinkInfo -> ShowS)
-> (ChatInviteLinkInfo -> String)
-> ([ChatInviteLinkInfo] -> ShowS)
-> Show ChatInviteLinkInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatInviteLinkInfo] -> ShowS
$cshowList :: [ChatInviteLinkInfo] -> ShowS
show :: ChatInviteLinkInfo -> String
$cshow :: ChatInviteLinkInfo -> String
showsPrec :: I32 -> ChatInviteLinkInfo -> ShowS
$cshowsPrec :: I32 -> ChatInviteLinkInfo -> ShowS
Show, ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool
(ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool)
-> (ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool)
-> Eq ChatInviteLinkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool
$c/= :: ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool
== :: ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool
$c== :: ChatInviteLinkInfo -> ChatInviteLinkInfo -> Bool
Eq, (forall x. ChatInviteLinkInfo -> Rep ChatInviteLinkInfo x)
-> (forall x. Rep ChatInviteLinkInfo x -> ChatInviteLinkInfo)
-> Generic ChatInviteLinkInfo
forall x. Rep ChatInviteLinkInfo x -> ChatInviteLinkInfo
forall x. ChatInviteLinkInfo -> Rep ChatInviteLinkInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatInviteLinkInfo x -> ChatInviteLinkInfo
$cfrom :: forall x. ChatInviteLinkInfo -> Rep ChatInviteLinkInfo x
Generic)
-- | Describes a type of public chats
data PublicChatType
  = -- | The chat is public, because it has username
  PublicChatTypeHasUsername
    { 
    }
  | -- | The chat is public, because it is a location-based supergroup
  PublicChatTypeIsLocationBased
    { 
    }
  deriving (I32 -> PublicChatType -> ShowS
[PublicChatType] -> ShowS
PublicChatType -> String
(I32 -> PublicChatType -> ShowS)
-> (PublicChatType -> String)
-> ([PublicChatType] -> ShowS)
-> Show PublicChatType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicChatType] -> ShowS
$cshowList :: [PublicChatType] -> ShowS
show :: PublicChatType -> String
$cshow :: PublicChatType -> String
showsPrec :: I32 -> PublicChatType -> ShowS
$cshowsPrec :: I32 -> PublicChatType -> ShowS
Show, PublicChatType -> PublicChatType -> Bool
(PublicChatType -> PublicChatType -> Bool)
-> (PublicChatType -> PublicChatType -> Bool) -> Eq PublicChatType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicChatType -> PublicChatType -> Bool
$c/= :: PublicChatType -> PublicChatType -> Bool
== :: PublicChatType -> PublicChatType -> Bool
$c== :: PublicChatType -> PublicChatType -> Bool
Eq, (forall x. PublicChatType -> Rep PublicChatType x)
-> (forall x. Rep PublicChatType x -> PublicChatType)
-> Generic PublicChatType
forall x. Rep PublicChatType x -> PublicChatType
forall x. PublicChatType -> Rep PublicChatType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublicChatType x -> PublicChatType
$cfrom :: forall x. PublicChatType -> Rep PublicChatType x
Generic)
-- | Describes actions which should be possible to do through a chat action bar
data ChatActionBar
  = -- | The chat can be reported as spam using the method reportChat with the reason chatReportReasonSpam
  ChatActionBarReportSpam
    { 
    }
  | -- | The chat is a location-based supergroup, which can be reported as having unrelated location using the method reportChat with the reason chatReportReasonUnrelatedLocation
  ChatActionBarReportUnrelatedLocation
    { 
    }
  | -- | The chat is a private or secret chat, which can be reported using the method reportChat, or the other user can be added to the contact list using the method addContact, or the other user can be blocked using the method blockUser
  ChatActionBarReportAddBlock
    { 
    }
  | -- | The chat is a private or secret chat and the other user can be added to the contact list using the method addContact
  ChatActionBarAddContact
    { 
    }
  | -- | The chat is a private or secret chat with a mutual contact and the user's phone number can be shared with the other user using the method sharePhoneNumber
  ChatActionBarSharePhoneNumber
    { 
    }
  deriving (I32 -> ChatActionBar -> ShowS
[ChatActionBar] -> ShowS
ChatActionBar -> String
(I32 -> ChatActionBar -> ShowS)
-> (ChatActionBar -> String)
-> ([ChatActionBar] -> ShowS)
-> Show ChatActionBar
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatActionBar] -> ShowS
$cshowList :: [ChatActionBar] -> ShowS
show :: ChatActionBar -> String
$cshow :: ChatActionBar -> String
showsPrec :: I32 -> ChatActionBar -> ShowS
$cshowsPrec :: I32 -> ChatActionBar -> ShowS
Show, ChatActionBar -> ChatActionBar -> Bool
(ChatActionBar -> ChatActionBar -> Bool)
-> (ChatActionBar -> ChatActionBar -> Bool) -> Eq ChatActionBar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatActionBar -> ChatActionBar -> Bool
$c/= :: ChatActionBar -> ChatActionBar -> Bool
== :: ChatActionBar -> ChatActionBar -> Bool
$c== :: ChatActionBar -> ChatActionBar -> Bool
Eq, (forall x. ChatActionBar -> Rep ChatActionBar x)
-> (forall x. Rep ChatActionBar x -> ChatActionBar)
-> Generic ChatActionBar
forall x. Rep ChatActionBar x -> ChatActionBar
forall x. ChatActionBar -> Rep ChatActionBar x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatActionBar x -> ChatActionBar
$cfrom :: forall x. ChatActionBar -> Rep ChatActionBar x
Generic)
-- | Describes a keyboard button type
data KeyboardButtonType
  = -- | A simple button, with text that should be sent when the button is pressed
  KeyboardButtonTypeText
    { 
    }
  | -- | A button that sends the user's phone number when pressed; available only in private chats
  KeyboardButtonTypeRequestPhoneNumber
    { 
    }
  | -- | A button that sends the user's location when pressed; available only in private chats
  KeyboardButtonTypeRequestLocation
    { 
    }
  | -- | A button that allows the user to create and send a poll when pressed; available only in private chats 
  KeyboardButtonTypeRequestPoll
    { -- | If true, only regular polls must be allowed to create 
      KeyboardButtonType -> Bool
force_regular_4 :: Bool,
      -- | If true, only polls in quiz mode must be allowed to create
      KeyboardButtonType -> Bool
force_quiz_4 :: Bool
    }
  deriving (I32 -> KeyboardButtonType -> ShowS
[KeyboardButtonType] -> ShowS
KeyboardButtonType -> String
(I32 -> KeyboardButtonType -> ShowS)
-> (KeyboardButtonType -> String)
-> ([KeyboardButtonType] -> ShowS)
-> Show KeyboardButtonType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyboardButtonType] -> ShowS
$cshowList :: [KeyboardButtonType] -> ShowS
show :: KeyboardButtonType -> String
$cshow :: KeyboardButtonType -> String
showsPrec :: I32 -> KeyboardButtonType -> ShowS
$cshowsPrec :: I32 -> KeyboardButtonType -> ShowS
Show, KeyboardButtonType -> KeyboardButtonType -> Bool
(KeyboardButtonType -> KeyboardButtonType -> Bool)
-> (KeyboardButtonType -> KeyboardButtonType -> Bool)
-> Eq KeyboardButtonType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyboardButtonType -> KeyboardButtonType -> Bool
$c/= :: KeyboardButtonType -> KeyboardButtonType -> Bool
== :: KeyboardButtonType -> KeyboardButtonType -> Bool
$c== :: KeyboardButtonType -> KeyboardButtonType -> Bool
Eq, (forall x. KeyboardButtonType -> Rep KeyboardButtonType x)
-> (forall x. Rep KeyboardButtonType x -> KeyboardButtonType)
-> Generic KeyboardButtonType
forall x. Rep KeyboardButtonType x -> KeyboardButtonType
forall x. KeyboardButtonType -> Rep KeyboardButtonType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeyboardButtonType x -> KeyboardButtonType
$cfrom :: forall x. KeyboardButtonType -> Rep KeyboardButtonType x
Generic)
data KeyboardButton
  = -- | Represents a single button in a bot keyboard 
  KeyboardButton
    { -- | Text of the button 
      KeyboardButton -> T
text_1 :: T,
      -- | Type of the button
      KeyboardButton -> KeyboardButtonType
type_1 :: KeyboardButtonType
    }
  deriving (I32 -> KeyboardButton -> ShowS
[KeyboardButton] -> ShowS
KeyboardButton -> String
(I32 -> KeyboardButton -> ShowS)
-> (KeyboardButton -> String)
-> ([KeyboardButton] -> ShowS)
-> Show KeyboardButton
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeyboardButton] -> ShowS
$cshowList :: [KeyboardButton] -> ShowS
show :: KeyboardButton -> String
$cshow :: KeyboardButton -> String
showsPrec :: I32 -> KeyboardButton -> ShowS
$cshowsPrec :: I32 -> KeyboardButton -> ShowS
Show, KeyboardButton -> KeyboardButton -> Bool
(KeyboardButton -> KeyboardButton -> Bool)
-> (KeyboardButton -> KeyboardButton -> Bool) -> Eq KeyboardButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyboardButton -> KeyboardButton -> Bool
$c/= :: KeyboardButton -> KeyboardButton -> Bool
== :: KeyboardButton -> KeyboardButton -> Bool
$c== :: KeyboardButton -> KeyboardButton -> Bool
Eq, (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)
-- | Describes the type of an inline keyboard button
data InlineKeyboardButtonType
  = -- | A button that opens a specified URL 
  InlineKeyboardButtonTypeUrl
    { -- | HTTP or tg:// URL to open
      InlineKeyboardButtonType -> T
url_1 :: T
    }
  | -- | A button that opens a specified URL and automatically logs in in current user if they allowed to do that 
  InlineKeyboardButtonTypeLoginUrl
    { -- | An HTTP URL to open 
      InlineKeyboardButtonType -> T
url_2 :: T,
      -- | Unique button identifier 
      InlineKeyboardButtonType -> I32
id_2 :: I32,
      -- | If non-empty, new text of the button in forwarded messages
      InlineKeyboardButtonType -> T
forward_text_2 :: T
    }
  | -- | A button that sends a special callback query to a bot 
  InlineKeyboardButtonTypeCallback
    { -- | Data to be sent to the bot via a callback query
      InlineKeyboardButtonType -> ByteString64
data_3 :: ByteString64
    }
  | -- | A button with a game that sends a special callback query to a bot. This button must be in the first column and row of the keyboard and can be attached only to a message with content of the type messageGame
  InlineKeyboardButtonTypeCallbackGame
    { 
    }
  | -- | A button that forces an inline query to the bot to be inserted in the input field 
  InlineKeyboardButtonTypeSwitchInline
    { -- | Inline query to be sent to the bot 
      InlineKeyboardButtonType -> T
query_5 :: T,
      -- | True, if the inline query should be sent from the current chat
      InlineKeyboardButtonType -> Bool
in_current_chat_5 :: Bool
    }
  | -- | A button to buy something. This button must be in the first column and row of the keyboard and can be attached only to a message with content of the type messageInvoice
  InlineKeyboardButtonTypeBuy
    { 
    }
  deriving (I32 -> InlineKeyboardButtonType -> ShowS
[InlineKeyboardButtonType] -> ShowS
InlineKeyboardButtonType -> String
(I32 -> InlineKeyboardButtonType -> ShowS)
-> (InlineKeyboardButtonType -> String)
-> ([InlineKeyboardButtonType] -> ShowS)
-> Show InlineKeyboardButtonType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineKeyboardButtonType] -> ShowS
$cshowList :: [InlineKeyboardButtonType] -> ShowS
show :: InlineKeyboardButtonType -> String
$cshow :: InlineKeyboardButtonType -> String
showsPrec :: I32 -> InlineKeyboardButtonType -> ShowS
$cshowsPrec :: I32 -> InlineKeyboardButtonType -> ShowS
Show, InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool
(InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool)
-> (InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool)
-> Eq InlineKeyboardButtonType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool
$c/= :: InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool
== :: InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool
$c== :: InlineKeyboardButtonType -> InlineKeyboardButtonType -> Bool
Eq, (forall x.
 InlineKeyboardButtonType -> Rep InlineKeyboardButtonType x)
-> (forall x.
    Rep InlineKeyboardButtonType x -> InlineKeyboardButtonType)
-> Generic InlineKeyboardButtonType
forall x.
Rep InlineKeyboardButtonType x -> InlineKeyboardButtonType
forall x.
InlineKeyboardButtonType -> Rep InlineKeyboardButtonType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InlineKeyboardButtonType x -> InlineKeyboardButtonType
$cfrom :: forall x.
InlineKeyboardButtonType -> Rep InlineKeyboardButtonType x
Generic)
data InlineKeyboardButton
  = -- | Represents a single button in an inline keyboard 
  InlineKeyboardButton
    { -- | Text of the button 
      InlineKeyboardButton -> T
text_1 :: T,
      -- | Type of the button
      InlineKeyboardButton -> InlineKeyboardButtonType
type_1 :: InlineKeyboardButtonType
    }
  deriving (I32 -> InlineKeyboardButton -> ShowS
[InlineKeyboardButton] -> ShowS
InlineKeyboardButton -> String
(I32 -> InlineKeyboardButton -> ShowS)
-> (InlineKeyboardButton -> String)
-> ([InlineKeyboardButton] -> ShowS)
-> Show InlineKeyboardButton
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineKeyboardButton] -> ShowS
$cshowList :: [InlineKeyboardButton] -> ShowS
show :: InlineKeyboardButton -> String
$cshow :: InlineKeyboardButton -> String
showsPrec :: I32 -> InlineKeyboardButton -> ShowS
$cshowsPrec :: I32 -> InlineKeyboardButton -> ShowS
Show, InlineKeyboardButton -> InlineKeyboardButton -> Bool
(InlineKeyboardButton -> InlineKeyboardButton -> Bool)
-> (InlineKeyboardButton -> InlineKeyboardButton -> Bool)
-> Eq InlineKeyboardButton
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineKeyboardButton -> InlineKeyboardButton -> Bool
$c/= :: InlineKeyboardButton -> InlineKeyboardButton -> Bool
== :: InlineKeyboardButton -> InlineKeyboardButton -> Bool
$c== :: InlineKeyboardButton -> InlineKeyboardButton -> Bool
Eq, (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)
-- | Contains a description of a custom keyboard and actions that can be done with it to quickly reply to bots
data ReplyMarkup
  = -- | Instructs clients to remove the keyboard once this message has been received. This kind of keyboard can't be received in an incoming message; instead, UpdateChatReplyMarkup with message_id == 0 will be sent
  ReplyMarkupRemoveKeyboard
    { -- | True, if the keyboard is removed only for the mentioned users or the target user of a reply
      ReplyMarkup -> Bool
is_personal_1 :: Bool
    }
  | -- | Instructs clients to force a reply to this message
  ReplyMarkupForceReply
    { -- | True, if a forced reply must automatically be shown to the current user. For outgoing messages, specify true to show the forced reply only for the mentioned users and for the target user of a reply
      ReplyMarkup -> Bool
is_personal_2 :: Bool
    }
  | -- | Contains a custom keyboard layout to quickly reply to bots
  ReplyMarkupShowKeyboard
    { -- | A list of rows of bot keyboard buttons
      ReplyMarkup -> [[KeyboardButton]]
rows_3 :: ([]) (([]) (KeyboardButton)),
      -- | True, if the client needs to resize the keyboard vertically
      ReplyMarkup -> Bool
resize_keyboard_3 :: Bool,
      -- | True, if the client needs to hide the keyboard after use
      ReplyMarkup -> Bool
one_time_3 :: Bool,
      -- | True, if the keyboard must automatically be shown to the current user. For outgoing messages, specify true to show the keyboard only for the mentioned users and for the target user of a reply
      ReplyMarkup -> Bool
is_personal_3 :: Bool
    }
  | -- | Contains an inline keyboard layout
  ReplyMarkupInlineKeyboard
    { -- | A list of rows of inline keyboard buttons
      ReplyMarkup -> [[InlineKeyboardButton]]
rows_4 :: ([]) (([]) (InlineKeyboardButton))
    }
  deriving (I32 -> ReplyMarkup -> ShowS
[ReplyMarkup] -> ShowS
ReplyMarkup -> String
(I32 -> ReplyMarkup -> ShowS)
-> (ReplyMarkup -> String)
-> ([ReplyMarkup] -> ShowS)
-> Show ReplyMarkup
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReplyMarkup] -> ShowS
$cshowList :: [ReplyMarkup] -> ShowS
show :: ReplyMarkup -> String
$cshow :: ReplyMarkup -> String
showsPrec :: I32 -> ReplyMarkup -> ShowS
$cshowsPrec :: I32 -> ReplyMarkup -> ShowS
Show, ReplyMarkup -> ReplyMarkup -> Bool
(ReplyMarkup -> ReplyMarkup -> Bool)
-> (ReplyMarkup -> ReplyMarkup -> Bool) -> Eq ReplyMarkup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReplyMarkup -> ReplyMarkup -> Bool
$c/= :: ReplyMarkup -> ReplyMarkup -> Bool
== :: ReplyMarkup -> ReplyMarkup -> Bool
$c== :: ReplyMarkup -> ReplyMarkup -> Bool
Eq, (forall x. ReplyMarkup -> Rep ReplyMarkup x)
-> (forall x. Rep ReplyMarkup x -> ReplyMarkup)
-> Generic ReplyMarkup
forall x. Rep ReplyMarkup x -> ReplyMarkup
forall x. ReplyMarkup -> Rep ReplyMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplyMarkup x -> ReplyMarkup
$cfrom :: forall x. ReplyMarkup -> Rep ReplyMarkup x
Generic)
-- | Contains information about an inline button of type inlineKeyboardButtonTypeLoginUrl
data LoginUrlInfo
  = -- | An HTTP url needs to be open 
  LoginUrlInfoOpen
    { -- | The URL to open 
      LoginUrlInfo -> T
url_1 :: T,
      -- | True, if there is no need to show an ordinary open URL confirm
      LoginUrlInfo -> Bool
skip_confirm_1 :: Bool
    }
  | -- | An authorization confirmation dialog needs to be shown to the user 
  LoginUrlInfoRequestConfirmation
    { -- | An HTTP URL to be opened 
      LoginUrlInfo -> T
url_2 :: T,
      -- | A domain of the URL
      LoginUrlInfo -> T
domain_2 :: T,
      -- | User identifier of a bot linked with the website 
      LoginUrlInfo -> I32
bot_user_id_2 :: I32,
      -- | True, if the user needs to be requested to give the permission to the bot to send them messages
      LoginUrlInfo -> Bool
request_write_access_2 :: Bool
    }
  deriving (I32 -> LoginUrlInfo -> ShowS
[LoginUrlInfo] -> ShowS
LoginUrlInfo -> String
(I32 -> LoginUrlInfo -> ShowS)
-> (LoginUrlInfo -> String)
-> ([LoginUrlInfo] -> ShowS)
-> Show LoginUrlInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LoginUrlInfo] -> ShowS
$cshowList :: [LoginUrlInfo] -> ShowS
show :: LoginUrlInfo -> String
$cshow :: LoginUrlInfo -> String
showsPrec :: I32 -> LoginUrlInfo -> ShowS
$cshowsPrec :: I32 -> LoginUrlInfo -> ShowS
Show, LoginUrlInfo -> LoginUrlInfo -> Bool
(LoginUrlInfo -> LoginUrlInfo -> Bool)
-> (LoginUrlInfo -> LoginUrlInfo -> Bool) -> Eq LoginUrlInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LoginUrlInfo -> LoginUrlInfo -> Bool
$c/= :: LoginUrlInfo -> LoginUrlInfo -> Bool
== :: LoginUrlInfo -> LoginUrlInfo -> Bool
$c== :: LoginUrlInfo -> LoginUrlInfo -> Bool
Eq, (forall x. LoginUrlInfo -> Rep LoginUrlInfo x)
-> (forall x. Rep LoginUrlInfo x -> LoginUrlInfo)
-> Generic LoginUrlInfo
forall x. Rep LoginUrlInfo x -> LoginUrlInfo
forall x. LoginUrlInfo -> Rep LoginUrlInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LoginUrlInfo x -> LoginUrlInfo
$cfrom :: forall x. LoginUrlInfo -> Rep LoginUrlInfo x
Generic)
-- | Describes a text object inside an instant-view web page
data RichText
  = -- | A plain text 
  RichTextPlain
    { -- | Text
      RichText -> T
text_1 :: T
    }
  | -- | A bold rich text 
  RichTextBold
    { -- | Text
      RichText -> RichText
text_2 :: RichText
    }
  | -- | An italicized rich text 
  RichTextItalic
    { -- | Text
      RichText -> RichText
text_3 :: RichText
    }
  | -- | An underlined rich text 
  RichTextUnderline
    { -- | Text
      RichText -> RichText
text_4 :: RichText
    }
  | -- | A strikethrough rich text 
  RichTextStrikethrough
    { -- | Text
      RichText -> RichText
text_5 :: RichText
    }
  | -- | A fixed-width rich text 
  RichTextFixed
    { -- | Text
      RichText -> RichText
text_6 :: RichText
    }
  | -- | A rich text URL link 
  RichTextUrl
    { -- | Text 
      RichText -> RichText
text_7 :: RichText,
      -- | URL 
      RichText -> T
url_7 :: T,
      -- | True, if the URL has cached instant view server-side
      RichText -> Bool
is_cached_7 :: Bool
    }
  | -- | A rich text email link 
  RichTextEmailAddress
    { -- | Text 
      RichText -> RichText
text_8 :: RichText,
      -- | Email address
      RichText -> T
email_address_8 :: T
    }
  | -- | A subscript rich text 
  RichTextSubscript
    { -- | Text
      RichText -> RichText
text_9 :: RichText
    }
  | -- | A superscript rich text 
  RichTextSuperscript
    { -- | Text
      RichText -> RichText
text_10 :: RichText
    }
  | -- | A marked rich text 
  RichTextMarked
    { -- | Text
      RichText -> RichText
text_11 :: RichText
    }
  | -- | A rich text phone number 
  RichTextPhoneNumber
    { -- | Text 
      RichText -> RichText
text_12 :: RichText,
      -- | Phone number
      RichText -> T
phone_number_12 :: T
    }
  | -- | A small image inside the text 
  RichTextIcon
    { -- | The image represented as a document. The image can be in GIF, JPEG or PNG format
      RichText -> Document
document_13 :: Document,
      -- | Width of a bounding box in which the image should be shown; 0 if unknown
      RichText -> I32
width_13 :: I32,
      -- | Height of a bounding box in which the image should be shown; 0 if unknown
      RichText -> I32
height_13 :: I32
    }
  | -- | A rich text reference of a text on the same web page 
  RichTextReference
    { -- | The text 
      RichText -> RichText
text_14 :: RichText,
      -- | The text to show on click 
      RichText -> RichText
reference_text_14 :: RichText,
      -- | An HTTP URL, opening the reference
      RichText -> T
url_14 :: T
    }
  | -- | An anchor 
  RichTextAnchor
    { -- | Anchor name
      RichText -> T
name_15 :: T
    }
  | -- | A link to an anchor on the same web page 
  RichTextAnchorLink
    { -- | The link text 
      RichText -> RichText
text_16 :: RichText,
      -- | The anchor name. If the name is empty, the link should bring back to top 
      RichText -> T
name_16 :: T,
      -- | An HTTP URL, opening the anchor
      RichText -> T
url_16 :: T
    }
  | -- | A concatenation of rich texts 
  RichTexts
    { -- | Texts
      RichText -> [RichText]
texts_17 :: ([]) (RichText)
    }
  deriving (I32 -> RichText -> ShowS
[RichText] -> ShowS
RichText -> String
(I32 -> RichText -> ShowS)
-> (RichText -> String) -> ([RichText] -> ShowS) -> Show RichText
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RichText] -> ShowS
$cshowList :: [RichText] -> ShowS
show :: RichText -> String
$cshow :: RichText -> String
showsPrec :: I32 -> RichText -> ShowS
$cshowsPrec :: I32 -> RichText -> ShowS
Show, RichText -> RichText -> Bool
(RichText -> RichText -> Bool)
-> (RichText -> RichText -> Bool) -> Eq RichText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RichText -> RichText -> Bool
$c/= :: RichText -> RichText -> Bool
== :: RichText -> RichText -> Bool
$c== :: RichText -> RichText -> Bool
Eq, (forall x. RichText -> Rep RichText x)
-> (forall x. Rep RichText x -> RichText) -> Generic RichText
forall x. Rep RichText x -> RichText
forall x. RichText -> Rep RichText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RichText x -> RichText
$cfrom :: forall x. RichText -> Rep RichText x
Generic)
data PageBlockCaption
  = -- | Contains a caption of an instant view web page block, consisting of a text and a trailing credit 
  PageBlockCaption
    { -- | Content of the caption 
      PageBlockCaption -> RichText
text_1 :: RichText,
      -- | Block credit (like HTML tag <cite>)
      PageBlockCaption -> RichText
credit_1 :: RichText
    }
  deriving (I32 -> PageBlockCaption -> ShowS
[PageBlockCaption] -> ShowS
PageBlockCaption -> String
(I32 -> PageBlockCaption -> ShowS)
-> (PageBlockCaption -> String)
-> ([PageBlockCaption] -> ShowS)
-> Show PageBlockCaption
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockCaption] -> ShowS
$cshowList :: [PageBlockCaption] -> ShowS
show :: PageBlockCaption -> String
$cshow :: PageBlockCaption -> String
showsPrec :: I32 -> PageBlockCaption -> ShowS
$cshowsPrec :: I32 -> PageBlockCaption -> ShowS
Show, PageBlockCaption -> PageBlockCaption -> Bool
(PageBlockCaption -> PageBlockCaption -> Bool)
-> (PageBlockCaption -> PageBlockCaption -> Bool)
-> Eq PageBlockCaption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockCaption -> PageBlockCaption -> Bool
$c/= :: PageBlockCaption -> PageBlockCaption -> Bool
== :: PageBlockCaption -> PageBlockCaption -> Bool
$c== :: PageBlockCaption -> PageBlockCaption -> Bool
Eq, (forall x. PageBlockCaption -> Rep PageBlockCaption x)
-> (forall x. Rep PageBlockCaption x -> PageBlockCaption)
-> Generic PageBlockCaption
forall x. Rep PageBlockCaption x -> PageBlockCaption
forall x. PageBlockCaption -> Rep PageBlockCaption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageBlockCaption x -> PageBlockCaption
$cfrom :: forall x. PageBlockCaption -> Rep PageBlockCaption x
Generic)
data PageBlockListItem
  = -- | Describes an item of a list page block 
  PageBlockListItem
    { -- | Item label 
      PageBlockListItem -> T
label_1 :: T,
      -- | Item blocks
      PageBlockListItem -> [PageBlock]
page_blocks_1 :: ([]) (PageBlock)
    }
  deriving (I32 -> PageBlockListItem -> ShowS
[PageBlockListItem] -> ShowS
PageBlockListItem -> String
(I32 -> PageBlockListItem -> ShowS)
-> (PageBlockListItem -> String)
-> ([PageBlockListItem] -> ShowS)
-> Show PageBlockListItem
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockListItem] -> ShowS
$cshowList :: [PageBlockListItem] -> ShowS
show :: PageBlockListItem -> String
$cshow :: PageBlockListItem -> String
showsPrec :: I32 -> PageBlockListItem -> ShowS
$cshowsPrec :: I32 -> PageBlockListItem -> ShowS
Show, PageBlockListItem -> PageBlockListItem -> Bool
(PageBlockListItem -> PageBlockListItem -> Bool)
-> (PageBlockListItem -> PageBlockListItem -> Bool)
-> Eq PageBlockListItem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockListItem -> PageBlockListItem -> Bool
$c/= :: PageBlockListItem -> PageBlockListItem -> Bool
== :: PageBlockListItem -> PageBlockListItem -> Bool
$c== :: PageBlockListItem -> PageBlockListItem -> Bool
Eq, (forall x. PageBlockListItem -> Rep PageBlockListItem x)
-> (forall x. Rep PageBlockListItem x -> PageBlockListItem)
-> Generic PageBlockListItem
forall x. Rep PageBlockListItem x -> PageBlockListItem
forall x. PageBlockListItem -> Rep PageBlockListItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageBlockListItem x -> PageBlockListItem
$cfrom :: forall x. PageBlockListItem -> Rep PageBlockListItem x
Generic)
-- | Describes a horizontal alignment of a table cell content
data PageBlockHorizontalAlignment
  = -- | The content should be left-aligned
  PageBlockHorizontalAlignmentLeft
    { 
    }
  | -- | The content should be center-aligned
  PageBlockHorizontalAlignmentCenter
    { 
    }
  | -- | The content should be right-aligned
  PageBlockHorizontalAlignmentRight
    { 
    }
  deriving (I32 -> PageBlockHorizontalAlignment -> ShowS
[PageBlockHorizontalAlignment] -> ShowS
PageBlockHorizontalAlignment -> String
(I32 -> PageBlockHorizontalAlignment -> ShowS)
-> (PageBlockHorizontalAlignment -> String)
-> ([PageBlockHorizontalAlignment] -> ShowS)
-> Show PageBlockHorizontalAlignment
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockHorizontalAlignment] -> ShowS
$cshowList :: [PageBlockHorizontalAlignment] -> ShowS
show :: PageBlockHorizontalAlignment -> String
$cshow :: PageBlockHorizontalAlignment -> String
showsPrec :: I32 -> PageBlockHorizontalAlignment -> ShowS
$cshowsPrec :: I32 -> PageBlockHorizontalAlignment -> ShowS
Show, PageBlockHorizontalAlignment
-> PageBlockHorizontalAlignment -> Bool
(PageBlockHorizontalAlignment
 -> PageBlockHorizontalAlignment -> Bool)
-> (PageBlockHorizontalAlignment
    -> PageBlockHorizontalAlignment -> Bool)
-> Eq PageBlockHorizontalAlignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockHorizontalAlignment
-> PageBlockHorizontalAlignment -> Bool
$c/= :: PageBlockHorizontalAlignment
-> PageBlockHorizontalAlignment -> Bool
== :: PageBlockHorizontalAlignment
-> PageBlockHorizontalAlignment -> Bool
$c== :: PageBlockHorizontalAlignment
-> PageBlockHorizontalAlignment -> Bool
Eq, (forall x.
 PageBlockHorizontalAlignment -> Rep PageBlockHorizontalAlignment x)
-> (forall x.
    Rep PageBlockHorizontalAlignment x -> PageBlockHorizontalAlignment)
-> Generic PageBlockHorizontalAlignment
forall x.
Rep PageBlockHorizontalAlignment x -> PageBlockHorizontalAlignment
forall x.
PageBlockHorizontalAlignment -> Rep PageBlockHorizontalAlignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PageBlockHorizontalAlignment x -> PageBlockHorizontalAlignment
$cfrom :: forall x.
PageBlockHorizontalAlignment -> Rep PageBlockHorizontalAlignment x
Generic)
-- | Describes a Vertical alignment of a table cell content
data PageBlockVerticalAlignment
  = -- | The content should be top-aligned
  PageBlockVerticalAlignmentTop
    { 
    }
  | -- | The content should be middle-aligned
  PageBlockVerticalAlignmentMiddle
    { 
    }
  | -- | The content should be bottom-aligned
  PageBlockVerticalAlignmentBottom
    { 
    }
  deriving (I32 -> PageBlockVerticalAlignment -> ShowS
[PageBlockVerticalAlignment] -> ShowS
PageBlockVerticalAlignment -> String
(I32 -> PageBlockVerticalAlignment -> ShowS)
-> (PageBlockVerticalAlignment -> String)
-> ([PageBlockVerticalAlignment] -> ShowS)
-> Show PageBlockVerticalAlignment
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockVerticalAlignment] -> ShowS
$cshowList :: [PageBlockVerticalAlignment] -> ShowS
show :: PageBlockVerticalAlignment -> String
$cshow :: PageBlockVerticalAlignment -> String
showsPrec :: I32 -> PageBlockVerticalAlignment -> ShowS
$cshowsPrec :: I32 -> PageBlockVerticalAlignment -> ShowS
Show, PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool
(PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool)
-> (PageBlockVerticalAlignment
    -> PageBlockVerticalAlignment -> Bool)
-> Eq PageBlockVerticalAlignment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool
$c/= :: PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool
== :: PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool
$c== :: PageBlockVerticalAlignment -> PageBlockVerticalAlignment -> Bool
Eq, (forall x.
 PageBlockVerticalAlignment -> Rep PageBlockVerticalAlignment x)
-> (forall x.
    Rep PageBlockVerticalAlignment x -> PageBlockVerticalAlignment)
-> Generic PageBlockVerticalAlignment
forall x.
Rep PageBlockVerticalAlignment x -> PageBlockVerticalAlignment
forall x.
PageBlockVerticalAlignment -> Rep PageBlockVerticalAlignment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PageBlockVerticalAlignment x -> PageBlockVerticalAlignment
$cfrom :: forall x.
PageBlockVerticalAlignment -> Rep PageBlockVerticalAlignment x
Generic)
data PageBlockTableCell
  = -- | Represents a cell of a table 
  PageBlockTableCell
    { -- | Cell text; may be null. If the text is null, then the cell should be invisible 
      PageBlockTableCell -> RichText
text_1 :: RichText,
      -- | True, if it is a header cell
      PageBlockTableCell -> Bool
is_header_1 :: Bool,
      -- | The number of columns the cell should span 
      PageBlockTableCell -> I32
colspan_1 :: I32,
      -- | The number of rows the cell should span
      PageBlockTableCell -> I32
rowspan_1 :: I32,
      -- | Horizontal cell content alignment 
      PageBlockTableCell -> PageBlockHorizontalAlignment
align_1 :: PageBlockHorizontalAlignment,
      -- | Vertical cell content alignment
      PageBlockTableCell -> PageBlockVerticalAlignment
valign_1 :: PageBlockVerticalAlignment
    }
  deriving (I32 -> PageBlockTableCell -> ShowS
[PageBlockTableCell] -> ShowS
PageBlockTableCell -> String
(I32 -> PageBlockTableCell -> ShowS)
-> (PageBlockTableCell -> String)
-> ([PageBlockTableCell] -> ShowS)
-> Show PageBlockTableCell
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockTableCell] -> ShowS
$cshowList :: [PageBlockTableCell] -> ShowS
show :: PageBlockTableCell -> String
$cshow :: PageBlockTableCell -> String
showsPrec :: I32 -> PageBlockTableCell -> ShowS
$cshowsPrec :: I32 -> PageBlockTableCell -> ShowS
Show, PageBlockTableCell -> PageBlockTableCell -> Bool
(PageBlockTableCell -> PageBlockTableCell -> Bool)
-> (PageBlockTableCell -> PageBlockTableCell -> Bool)
-> Eq PageBlockTableCell
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockTableCell -> PageBlockTableCell -> Bool
$c/= :: PageBlockTableCell -> PageBlockTableCell -> Bool
== :: PageBlockTableCell -> PageBlockTableCell -> Bool
$c== :: PageBlockTableCell -> PageBlockTableCell -> Bool
Eq, (forall x. PageBlockTableCell -> Rep PageBlockTableCell x)
-> (forall x. Rep PageBlockTableCell x -> PageBlockTableCell)
-> Generic PageBlockTableCell
forall x. Rep PageBlockTableCell x -> PageBlockTableCell
forall x. PageBlockTableCell -> Rep PageBlockTableCell x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageBlockTableCell x -> PageBlockTableCell
$cfrom :: forall x. PageBlockTableCell -> Rep PageBlockTableCell x
Generic)
data PageBlockRelatedArticle
  = -- | Contains information about a related article 
  PageBlockRelatedArticle
    { -- | Related article URL 
      PageBlockRelatedArticle -> T
url_1 :: T,
      -- | Article title; may be empty 
      PageBlockRelatedArticle -> T
title_1 :: T,
      -- | Contains information about a related article 
      PageBlockRelatedArticle -> T
description_1 :: T,
      -- | Article photo; may be null 
      PageBlockRelatedArticle -> Photo
photo_1 :: Photo,
      -- | Article author; may be empty 
      PageBlockRelatedArticle -> T
author_1 :: T,
      -- | Point in time (Unix timestamp) when the article was published; 0 if unknown
      PageBlockRelatedArticle -> I32
publish_date_1 :: I32
    }
  deriving (I32 -> PageBlockRelatedArticle -> ShowS
[PageBlockRelatedArticle] -> ShowS
PageBlockRelatedArticle -> String
(I32 -> PageBlockRelatedArticle -> ShowS)
-> (PageBlockRelatedArticle -> String)
-> ([PageBlockRelatedArticle] -> ShowS)
-> Show PageBlockRelatedArticle
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlockRelatedArticle] -> ShowS
$cshowList :: [PageBlockRelatedArticle] -> ShowS
show :: PageBlockRelatedArticle -> String
$cshow :: PageBlockRelatedArticle -> String
showsPrec :: I32 -> PageBlockRelatedArticle -> ShowS
$cshowsPrec :: I32 -> PageBlockRelatedArticle -> ShowS
Show, PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool
(PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool)
-> (PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool)
-> Eq PageBlockRelatedArticle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool
$c/= :: PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool
== :: PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool
$c== :: PageBlockRelatedArticle -> PageBlockRelatedArticle -> Bool
Eq, (forall x.
 PageBlockRelatedArticle -> Rep PageBlockRelatedArticle x)
-> (forall x.
    Rep PageBlockRelatedArticle x -> PageBlockRelatedArticle)
-> Generic PageBlockRelatedArticle
forall x. Rep PageBlockRelatedArticle x -> PageBlockRelatedArticle
forall x. PageBlockRelatedArticle -> Rep PageBlockRelatedArticle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageBlockRelatedArticle x -> PageBlockRelatedArticle
$cfrom :: forall x. PageBlockRelatedArticle -> Rep PageBlockRelatedArticle x
Generic)
-- | Describes a block of an instant view web page
data PageBlock
  = -- | The title of a page 
  PageBlockTitle
    { -- | Title
      PageBlock -> RichText
title_1 :: RichText
    }
  | -- | The subtitle of a page 
  PageBlockSubtitle
    { -- | Subtitle
      PageBlock -> RichText
subtitle_2 :: RichText
    }
  | -- | The author and publishing date of a page 
  PageBlockAuthorDate
    { -- | Author 
      PageBlock -> RichText
author_3 :: RichText,
      -- | Point in time (Unix timestamp) when the article was published; 0 if unknown
      PageBlock -> I32
publish_date_3 :: I32
    }
  | -- | A header 
  PageBlockHeader
    { -- | Header
      PageBlock -> RichText
header_4 :: RichText
    }
  | -- | A subheader 
  PageBlockSubheader
    { -- | Subheader
      PageBlock -> RichText
subheader_5 :: RichText
    }
  | -- | A kicker 
  PageBlockKicker
    { -- | Kicker
      PageBlock -> RichText
kicker_6 :: RichText
    }
  | -- | A text paragraph 
  PageBlockParagraph
    { -- | Paragraph text
      PageBlock -> RichText
text_7 :: RichText
    }
  | -- | A preformatted text paragraph 
  PageBlockPreformatted
    { -- | Paragraph text 
      PageBlock -> RichText
text_8 :: RichText,
      -- | Programming language for which the text should be formatted
      PageBlock -> T
language_8 :: T
    }
  | -- | The footer of a page 
  PageBlockFooter
    { -- | Footer
      PageBlock -> RichText
footer_9 :: RichText
    }
  | -- | An empty block separating a page
  PageBlockDivider
    { 
    }
  | -- | An invisible anchor on a page, which can be used in a URL to open the page from the specified anchor 
  PageBlockAnchor
    { -- | Name of the anchor
      PageBlock -> T
name_11 :: T
    }
  | -- | A list of data blocks 
  PageBlockList
    { -- | The items of the list
      PageBlock -> [PageBlockListItem]
items_12 :: ([]) (PageBlockListItem)
    }
  | -- | A block quote 
  PageBlockBlockQuote
    { -- | Quote text 
      PageBlock -> RichText
text_13 :: RichText,
      -- | Quote credit
      PageBlock -> RichText
credit_13 :: RichText
    }
  | -- | A pull quote 
  PageBlockPullQuote
    { -- | Quote text 
      PageBlock -> RichText
text_14 :: RichText,
      -- | Quote credit
      PageBlock -> RichText
credit_14 :: RichText
    }
  | -- | An animation 
  PageBlockAnimation
    { -- | Animation file; may be null 
      PageBlock -> Animation
animation_15 :: Animation,
      -- | Animation caption 
      PageBlock -> PageBlockCaption
caption_15 :: PageBlockCaption,
      -- | True, if the animation should be played automatically
      PageBlock -> Bool
need_autoplay_15 :: Bool
    }
  | -- | An audio file 
  PageBlockAudio
    { -- | Audio file; may be null 
      PageBlock -> Audio
audio_16 :: Audio,
      -- | Audio file caption
      PageBlock -> PageBlockCaption
caption_16 :: PageBlockCaption
    }
  | -- | A photo 
  PageBlockPhoto
    { -- | Photo file; may be null 
      PageBlock -> Photo
photo_17 :: Photo,
      -- | Photo caption 
      PageBlock -> PageBlockCaption
caption_17 :: PageBlockCaption,
      -- | URL that needs to be opened when the photo is clicked
      PageBlock -> T
url_17 :: T
    }
  | -- | A video 
  PageBlockVideo
    { -- | Video file; may be null 
      PageBlock -> Video
video_18 :: Video,
      -- | Video caption 
      PageBlock -> PageBlockCaption
caption_18 :: PageBlockCaption,
      -- | True, if the video should be played automatically 
      PageBlock -> Bool
need_autoplay_18 :: Bool,
      -- | True, if the video should be looped
      PageBlock -> Bool
is_looped_18 :: Bool
    }
  | -- | A voice note 
  PageBlockVoiceNote
    { -- | Voice note; may be null 
      PageBlock -> VoiceNote
voice_note_19 :: VoiceNote,
      -- | Voice note caption
      PageBlock -> PageBlockCaption
caption_19 :: PageBlockCaption
    }
  | -- | A page cover 
  PageBlockCover
    { -- | Cover
      PageBlock -> PageBlock
cover_20 :: PageBlock
    }
  | -- | An embedded web page 
  PageBlockEmbedded
    { -- | Web page URL, if available 
      PageBlock -> T
url_21 :: T,
      -- | HTML-markup of the embedded page 
      PageBlock -> T
html_21 :: T,
      -- | Poster photo, if available; may be null 
      PageBlock -> Photo
poster_photo_21 :: Photo,
      -- | Block width; 0 if unknown 
      PageBlock -> I32
width_21 :: I32,
      -- | Block height; 0 if unknown 
      PageBlock -> I32
height_21 :: I32,
      -- | Block caption 
      PageBlock -> PageBlockCaption
caption_21 :: PageBlockCaption,
      -- | True, if the block should be full width 
      PageBlock -> Bool
is_full_width_21 :: Bool,
      -- | True, if scrolling should be allowed
      PageBlock -> Bool
allow_scrolling_21 :: Bool
    }
  | -- | An embedded post 
  PageBlockEmbeddedPost
    { -- | Web page URL 
      PageBlock -> T
url_22 :: T,
      -- | Post author 
      PageBlock -> T
author_22 :: T,
      -- | Post author photo; may be null 
      PageBlock -> Photo
author_photo_22 :: Photo,
      -- | Point in time (Unix timestamp) when the post was created; 0 if unknown 
      PageBlock -> I32
date_22 :: I32,
      -- | Post content 
      PageBlock -> [PageBlock]
page_blocks_22 :: ([]) (PageBlock),
      -- | Post caption
      PageBlock -> PageBlockCaption
caption_22 :: PageBlockCaption
    }
  | -- | A collage 
  PageBlockCollage
    { -- | Collage item contents 
      PageBlock -> [PageBlock]
page_blocks_23 :: ([]) (PageBlock),
      -- | Block caption
      PageBlock -> PageBlockCaption
caption_23 :: PageBlockCaption
    }
  | -- | A slideshow 
  PageBlockSlideshow
    { -- | Slideshow item contents 
      PageBlock -> [PageBlock]
page_blocks_24 :: ([]) (PageBlock),
      -- | Block caption
      PageBlock -> PageBlockCaption
caption_24 :: PageBlockCaption
    }
  | -- | A link to a chat 
  PageBlockChatLink
    { -- | Chat title 
      PageBlock -> T
title_25 :: T,
      -- | Chat photo; may be null 
      PageBlock -> ChatPhoto
photo_25 :: ChatPhoto,
      -- | Chat username, by which all other information about the chat should be resolved
      PageBlock -> T
username_25 :: T
    }
  | -- | A table 
  PageBlockTable
    { -- | Table caption 
      PageBlock -> RichText
caption_26 :: RichText,
      -- | Table cells 
      PageBlock -> [[PageBlockTableCell]]
cells_26 :: ([]) (([]) (PageBlockTableCell)),
      -- | True, if the table is bordered 
      PageBlock -> Bool
is_bordered_26 :: Bool,
      -- | True, if the table is striped
      PageBlock -> Bool
is_striped_26 :: Bool
    }
  | -- | A collapsible block 
  PageBlockDetails
    { -- | Always visible heading for the block 
      PageBlock -> RichText
header_27 :: RichText,
      -- | Block contents 
      PageBlock -> [PageBlock]
page_blocks_27 :: ([]) (PageBlock),
      -- | True, if the block is open by default
      PageBlock -> Bool
is_open_27 :: Bool
    }
  | -- | Related articles 
  PageBlockRelatedArticles
    { -- | Block header 
      PageBlock -> RichText
header_28 :: RichText,
      -- | List of related articles
      PageBlock -> [PageBlockRelatedArticle]
articles_28 :: ([]) (PageBlockRelatedArticle)
    }
  | -- | A map 
  PageBlockMap
    { -- | Location of the map center 
      PageBlock -> Location
location_29 :: Location,
      -- | Map zoom level 
      PageBlock -> I32
zoom_29 :: I32,
      -- | Map width 
      PageBlock -> I32
width_29 :: I32,
      -- | Map height 
      PageBlock -> I32
height_29 :: I32,
      -- | Block caption
      PageBlock -> PageBlockCaption
caption_29 :: PageBlockCaption
    }
  deriving (I32 -> PageBlock -> ShowS
[PageBlock] -> ShowS
PageBlock -> String
(I32 -> PageBlock -> ShowS)
-> (PageBlock -> String)
-> ([PageBlock] -> ShowS)
-> Show PageBlock
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PageBlock] -> ShowS
$cshowList :: [PageBlock] -> ShowS
show :: PageBlock -> String
$cshow :: PageBlock -> String
showsPrec :: I32 -> PageBlock -> ShowS
$cshowsPrec :: I32 -> PageBlock -> ShowS
Show, PageBlock -> PageBlock -> Bool
(PageBlock -> PageBlock -> Bool)
-> (PageBlock -> PageBlock -> Bool) -> Eq PageBlock
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageBlock -> PageBlock -> Bool
$c/= :: PageBlock -> PageBlock -> Bool
== :: PageBlock -> PageBlock -> Bool
$c== :: PageBlock -> PageBlock -> Bool
Eq, (forall x. PageBlock -> Rep PageBlock x)
-> (forall x. Rep PageBlock x -> PageBlock) -> Generic PageBlock
forall x. Rep PageBlock x -> PageBlock
forall x. PageBlock -> Rep PageBlock x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PageBlock x -> PageBlock
$cfrom :: forall x. PageBlock -> Rep PageBlock x
Generic)
data WebPageInstantView
  = -- | Describes an instant view page for a web page
  WebPageInstantView
    { -- | Content of the web page
      WebPageInstantView -> [PageBlock]
page_blocks_1 :: ([]) (PageBlock),
      -- | Number of the instant view views; 0 if unknown
      WebPageInstantView -> I32
view_count_1 :: I32,
      -- | Version of the instant view, currently can be 1 or 2
      WebPageInstantView -> I32
version_1 :: I32,
      -- | True, if the instant view must be shown from right to left
      WebPageInstantView -> Bool
is_rtl_1 :: Bool,
      -- | True, if the instant view contains the full page. A network request might be needed to get the full web page instant view
      WebPageInstantView -> Bool
is_full_1 :: Bool
    }
  deriving (I32 -> WebPageInstantView -> ShowS
[WebPageInstantView] -> ShowS
WebPageInstantView -> String
(I32 -> WebPageInstantView -> ShowS)
-> (WebPageInstantView -> String)
-> ([WebPageInstantView] -> ShowS)
-> Show WebPageInstantView
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebPageInstantView] -> ShowS
$cshowList :: [WebPageInstantView] -> ShowS
show :: WebPageInstantView -> String
$cshow :: WebPageInstantView -> String
showsPrec :: I32 -> WebPageInstantView -> ShowS
$cshowsPrec :: I32 -> WebPageInstantView -> ShowS
Show, WebPageInstantView -> WebPageInstantView -> Bool
(WebPageInstantView -> WebPageInstantView -> Bool)
-> (WebPageInstantView -> WebPageInstantView -> Bool)
-> Eq WebPageInstantView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebPageInstantView -> WebPageInstantView -> Bool
$c/= :: WebPageInstantView -> WebPageInstantView -> Bool
== :: WebPageInstantView -> WebPageInstantView -> Bool
$c== :: WebPageInstantView -> WebPageInstantView -> Bool
Eq, (forall x. WebPageInstantView -> Rep WebPageInstantView x)
-> (forall x. Rep WebPageInstantView x -> WebPageInstantView)
-> Generic WebPageInstantView
forall x. Rep WebPageInstantView x -> WebPageInstantView
forall x. WebPageInstantView -> Rep WebPageInstantView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebPageInstantView x -> WebPageInstantView
$cfrom :: forall x. WebPageInstantView -> Rep WebPageInstantView x
Generic)
data WebPage
  = -- | Describes a web page preview
  WebPage
    { -- | Original URL of the link
      WebPage -> T
url_1 :: T,
      -- | URL to display
      WebPage -> T
display_url_1 :: T,
      -- | Type of the web page. Can be: article, photo, audio, video, document, profile, app, or something else
      WebPage -> T
type_1 :: T,
      -- | Short name of the site (e.g., Google Docs, App Store)
      WebPage -> T
site_name_1 :: T,
      -- | Title of the content
      WebPage -> T
title_1 :: T,
      -- | Describes a web page preview
      WebPage -> FormattedText
description_1 :: FormattedText,
      -- | Image representing the content; may be null
      WebPage -> Photo
photo_1 :: Photo,
      -- | URL to show in the embedded preview
      WebPage -> T
embed_url_1 :: T,
      -- | MIME type of the embedded preview, (e.g., text/html or video/mp4)
      WebPage -> T
embed_type_1 :: T,
      -- | Width of the embedded preview
      WebPage -> I32
embed_width_1 :: I32,
      -- | Height of the embedded preview
      WebPage -> I32
embed_height_1 :: I32,
      -- | Duration of the content, in seconds
      WebPage -> I32
duration_1 :: I32,
      -- | Author of the content
      WebPage -> T
author_1 :: T,
      -- | Preview of the content as an animation, if available; may be null
      WebPage -> Animation
animation_1 :: Animation,
      -- | Preview of the content as an audio file, if available; may be null
      WebPage -> Audio
audio_1 :: Audio,
      -- | Preview of the content as a document, if available (currently only available for small PDF files and ZIP archives); may be null
      WebPage -> Document
document_1 :: Document,
      -- | Preview of the content as a sticker for small WEBP files, if available; may be null
      WebPage -> Sticker
sticker_1 :: Sticker,
      -- | Preview of the content as a video, if available; may be null
      WebPage -> Video
video_1 :: Video,
      -- | Preview of the content as a video note, if available; may be null
      WebPage -> VideoNote
video_note_1 :: VideoNote,
      -- | Preview of the content as a voice note, if available; may be null
      WebPage -> VoiceNote
voice_note_1 :: VoiceNote,
      -- | Version of instant view, available for the web page (currently can be 1 or 2), 0 if none
      WebPage -> I32
instant_view_version_1 :: I32
    }
  deriving (I32 -> WebPage -> ShowS
[WebPage] -> ShowS
WebPage -> String
(I32 -> WebPage -> ShowS)
-> (WebPage -> String) -> ([WebPage] -> ShowS) -> Show WebPage
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WebPage] -> ShowS
$cshowList :: [WebPage] -> ShowS
show :: WebPage -> String
$cshow :: WebPage -> String
showsPrec :: I32 -> WebPage -> ShowS
$cshowsPrec :: I32 -> WebPage -> ShowS
Show, WebPage -> WebPage -> Bool
(WebPage -> WebPage -> Bool)
-> (WebPage -> WebPage -> Bool) -> Eq WebPage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WebPage -> WebPage -> Bool
$c/= :: WebPage -> WebPage -> Bool
== :: WebPage -> WebPage -> Bool
$c== :: WebPage -> WebPage -> Bool
Eq, (forall x. WebPage -> Rep WebPage x)
-> (forall x. Rep WebPage x -> WebPage) -> Generic WebPage
forall x. Rep WebPage x -> WebPage
forall x. WebPage -> Rep WebPage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WebPage x -> WebPage
$cfrom :: forall x. WebPage -> Rep WebPage x
Generic)
data BankCardActionOpenUrl
  = -- | Describes an action associated with a bank card number 
  BankCardActionOpenUrl
    { -- | Action text 
      BankCardActionOpenUrl -> T
text_1 :: T,
      -- | The URL to be opened
      BankCardActionOpenUrl -> T
url_1 :: T
    }
  deriving (I32 -> BankCardActionOpenUrl -> ShowS
[BankCardActionOpenUrl] -> ShowS
BankCardActionOpenUrl -> String
(I32 -> BankCardActionOpenUrl -> ShowS)
-> (BankCardActionOpenUrl -> String)
-> ([BankCardActionOpenUrl] -> ShowS)
-> Show BankCardActionOpenUrl
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BankCardActionOpenUrl] -> ShowS
$cshowList :: [BankCardActionOpenUrl] -> ShowS
show :: BankCardActionOpenUrl -> String
$cshow :: BankCardActionOpenUrl -> String
showsPrec :: I32 -> BankCardActionOpenUrl -> ShowS
$cshowsPrec :: I32 -> BankCardActionOpenUrl -> ShowS
Show, BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool
(BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool)
-> (BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool)
-> Eq BankCardActionOpenUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool
$c/= :: BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool
== :: BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool
$c== :: BankCardActionOpenUrl -> BankCardActionOpenUrl -> Bool
Eq, (forall x. BankCardActionOpenUrl -> Rep BankCardActionOpenUrl x)
-> (forall x. Rep BankCardActionOpenUrl x -> BankCardActionOpenUrl)
-> Generic BankCardActionOpenUrl
forall x. Rep BankCardActionOpenUrl x -> BankCardActionOpenUrl
forall x. BankCardActionOpenUrl -> Rep BankCardActionOpenUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BankCardActionOpenUrl x -> BankCardActionOpenUrl
$cfrom :: forall x. BankCardActionOpenUrl -> Rep BankCardActionOpenUrl x
Generic)
data BankCardInfo
  = -- | Information about a bank card 
  BankCardInfo
    { -- | Title of the bank card description 
      BankCardInfo -> T
title_1 :: T,
      -- | Actions that can be done with the bank card number
      BankCardInfo -> [BankCardActionOpenUrl]
actions_1 :: ([]) (BankCardActionOpenUrl)
    }
  deriving (I32 -> BankCardInfo -> ShowS
[BankCardInfo] -> ShowS
BankCardInfo -> String
(I32 -> BankCardInfo -> ShowS)
-> (BankCardInfo -> String)
-> ([BankCardInfo] -> ShowS)
-> Show BankCardInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BankCardInfo] -> ShowS
$cshowList :: [BankCardInfo] -> ShowS
show :: BankCardInfo -> String
$cshow :: BankCardInfo -> String
showsPrec :: I32 -> BankCardInfo -> ShowS
$cshowsPrec :: I32 -> BankCardInfo -> ShowS
Show, BankCardInfo -> BankCardInfo -> Bool
(BankCardInfo -> BankCardInfo -> Bool)
-> (BankCardInfo -> BankCardInfo -> Bool) -> Eq BankCardInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BankCardInfo -> BankCardInfo -> Bool
$c/= :: BankCardInfo -> BankCardInfo -> Bool
== :: BankCardInfo -> BankCardInfo -> Bool
$c== :: BankCardInfo -> BankCardInfo -> Bool
Eq, (forall x. BankCardInfo -> Rep BankCardInfo x)
-> (forall x. Rep BankCardInfo x -> BankCardInfo)
-> Generic BankCardInfo
forall x. Rep BankCardInfo x -> BankCardInfo
forall x. BankCardInfo -> Rep BankCardInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BankCardInfo x -> BankCardInfo
$cfrom :: forall x. BankCardInfo -> Rep BankCardInfo x
Generic)
data Address
  = -- | Describes an address 
  Address
    { -- | A two-letter ISO 3166-1 alpha-2 country code 
      Address -> T
country_code_1 :: T,
      -- | State, if applicable 
      Address -> T
state_1 :: T,
      -- | City 
      Address -> T
city_1 :: T,
      -- | First line of the address 
      Address -> T
street_line1_1 :: T,
      -- | Second line of the address 
      Address -> T
street_line2_1 :: T,
      -- | Address postal code
      Address -> T
postal_code_1 :: T
    }
  deriving (I32 -> Address -> ShowS
[Address] -> ShowS
Address -> String
(I32 -> Address -> ShowS)
-> (Address -> String) -> ([Address] -> ShowS) -> Show Address
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Address] -> ShowS
$cshowList :: [Address] -> ShowS
show :: Address -> String
$cshow :: Address -> String
showsPrec :: I32 -> Address -> ShowS
$cshowsPrec :: I32 -> Address -> ShowS
Show, Address -> Address -> Bool
(Address -> Address -> Bool)
-> (Address -> Address -> Bool) -> Eq Address
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Address -> Address -> Bool
$c/= :: Address -> Address -> Bool
== :: Address -> Address -> Bool
$c== :: Address -> Address -> Bool
Eq, (forall x. Address -> Rep Address x)
-> (forall x. Rep Address x -> Address) -> Generic Address
forall x. Rep Address x -> Address
forall x. Address -> Rep Address x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Address x -> Address
$cfrom :: forall x. Address -> Rep Address x
Generic)
data LabeledPricePart
  = -- | Portion of the price of a product (e.g., "delivery cost", "tax amount") 
  LabeledPricePart
    { -- | Label for this portion of the product price 
      LabeledPricePart -> T
label_1 :: T,
      -- | Currency amount in minimal quantity of the currency
      LabeledPricePart -> I32
amount_1 :: I53
    }
  deriving (I32 -> LabeledPricePart -> ShowS
[LabeledPricePart] -> ShowS
LabeledPricePart -> String
(I32 -> LabeledPricePart -> ShowS)
-> (LabeledPricePart -> String)
-> ([LabeledPricePart] -> ShowS)
-> Show LabeledPricePart
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LabeledPricePart] -> ShowS
$cshowList :: [LabeledPricePart] -> ShowS
show :: LabeledPricePart -> String
$cshow :: LabeledPricePart -> String
showsPrec :: I32 -> LabeledPricePart -> ShowS
$cshowsPrec :: I32 -> LabeledPricePart -> ShowS
Show, LabeledPricePart -> LabeledPricePart -> Bool
(LabeledPricePart -> LabeledPricePart -> Bool)
-> (LabeledPricePart -> LabeledPricePart -> Bool)
-> Eq LabeledPricePart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LabeledPricePart -> LabeledPricePart -> Bool
$c/= :: LabeledPricePart -> LabeledPricePart -> Bool
== :: LabeledPricePart -> LabeledPricePart -> Bool
$c== :: LabeledPricePart -> LabeledPricePart -> Bool
Eq, (forall x. LabeledPricePart -> Rep LabeledPricePart x)
-> (forall x. Rep LabeledPricePart x -> LabeledPricePart)
-> Generic LabeledPricePart
forall x. Rep LabeledPricePart x -> LabeledPricePart
forall x. LabeledPricePart -> Rep LabeledPricePart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LabeledPricePart x -> LabeledPricePart
$cfrom :: forall x. LabeledPricePart -> Rep LabeledPricePart x
Generic)
data Invoice
  = -- | Product invoice 
  Invoice
    { -- | ISO 4217 currency code 
      Invoice -> T
currency_1 :: T,
      -- | A list of objects used to calculate the total price of the product 
      Invoice -> [LabeledPricePart]
price_parts_1 :: ([]) (LabeledPricePart),
      -- | True, if the payment is a test payment
      Invoice -> Bool
is_test_1 :: Bool,
      -- | True, if the user's name is needed for payment 
      Invoice -> Bool
need_name_1 :: Bool,
      -- | True, if the user's phone number is needed for payment 
      Invoice -> Bool
need_phone_number_1 :: Bool,
      -- | True, if the user's email address is needed for payment
      Invoice -> Bool
need_email_address_1 :: Bool,
      -- | True, if the user's shipping address is needed for payment 
      Invoice -> Bool
need_shipping_address_1 :: Bool,
      -- | True, if the user's phone number will be sent to the provider
      Invoice -> Bool
send_phone_number_to_provider_1 :: Bool,
      -- | True, if the user's email address will be sent to the provider 
      Invoice -> Bool
send_email_address_to_provider_1 :: Bool,
      -- | True, if the total price depends on the shipping method
      Invoice -> Bool
is_flexible_1 :: Bool
    }
  deriving (I32 -> Invoice -> ShowS
[Invoice] -> ShowS
Invoice -> String
(I32 -> Invoice -> ShowS)
-> (Invoice -> String) -> ([Invoice] -> ShowS) -> Show Invoice
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Invoice] -> ShowS
$cshowList :: [Invoice] -> ShowS
show :: Invoice -> String
$cshow :: Invoice -> String
showsPrec :: I32 -> Invoice -> ShowS
$cshowsPrec :: I32 -> Invoice -> ShowS
Show, Invoice -> Invoice -> Bool
(Invoice -> Invoice -> Bool)
-> (Invoice -> Invoice -> Bool) -> Eq Invoice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Invoice -> Invoice -> Bool
$c/= :: Invoice -> Invoice -> Bool
== :: Invoice -> Invoice -> Bool
$c== :: Invoice -> Invoice -> Bool
Eq, (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)
data OrderInfo
  = -- | Order information 
  OrderInfo
    { -- | Name of the user 
      OrderInfo -> T
name_1 :: T,
      -- | Phone number of the user 
      OrderInfo -> T
phone_number_1 :: T,
      -- | Email address of the user 
      OrderInfo -> T
email_address_1 :: T,
      -- | Shipping address for this order; may be null
      OrderInfo -> Address
shipping_address_1 :: Address
    }
  deriving (I32 -> OrderInfo -> ShowS
[OrderInfo] -> ShowS
OrderInfo -> String
(I32 -> OrderInfo -> ShowS)
-> (OrderInfo -> String)
-> ([OrderInfo] -> ShowS)
-> Show OrderInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OrderInfo] -> ShowS
$cshowList :: [OrderInfo] -> ShowS
show :: OrderInfo -> String
$cshow :: OrderInfo -> String
showsPrec :: I32 -> OrderInfo -> ShowS
$cshowsPrec :: I32 -> OrderInfo -> ShowS
Show, OrderInfo -> OrderInfo -> Bool
(OrderInfo -> OrderInfo -> Bool)
-> (OrderInfo -> OrderInfo -> Bool) -> Eq OrderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OrderInfo -> OrderInfo -> Bool
$c/= :: OrderInfo -> OrderInfo -> Bool
== :: OrderInfo -> OrderInfo -> Bool
$c== :: OrderInfo -> OrderInfo -> Bool
Eq, (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)
data ShippingOption
  = -- | One shipping option 
  ShippingOption
    { -- | Shipping option identifier 
      ShippingOption -> T
id_1 :: T,
      -- | Option title 
      ShippingOption -> T
title_1 :: T,
      -- | A list of objects used to calculate the total shipping costs
      ShippingOption -> [LabeledPricePart]
price_parts_1 :: ([]) (LabeledPricePart)
    }
  deriving (I32 -> ShippingOption -> ShowS
[ShippingOption] -> ShowS
ShippingOption -> String
(I32 -> ShippingOption -> ShowS)
-> (ShippingOption -> String)
-> ([ShippingOption] -> ShowS)
-> Show ShippingOption
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ShippingOption] -> ShowS
$cshowList :: [ShippingOption] -> ShowS
show :: ShippingOption -> String
$cshow :: ShippingOption -> String
showsPrec :: I32 -> ShippingOption -> ShowS
$cshowsPrec :: I32 -> ShippingOption -> ShowS
Show, ShippingOption -> ShippingOption -> Bool
(ShippingOption -> ShippingOption -> Bool)
-> (ShippingOption -> ShippingOption -> Bool) -> Eq ShippingOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShippingOption -> ShippingOption -> Bool
$c/= :: ShippingOption -> ShippingOption -> Bool
== :: ShippingOption -> ShippingOption -> Bool
$c== :: ShippingOption -> ShippingOption -> Bool
Eq, (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)
data SavedCredentials
  = -- | Contains information about saved card credentials 
  SavedCredentials
    { -- | Unique identifier of the saved credentials 
      SavedCredentials -> T
id_1 :: T,
      -- | Title of the saved credentials
      SavedCredentials -> T
title_1 :: T
    }
  deriving (I32 -> SavedCredentials -> ShowS
[SavedCredentials] -> ShowS
SavedCredentials -> String
(I32 -> SavedCredentials -> ShowS)
-> (SavedCredentials -> String)
-> ([SavedCredentials] -> ShowS)
-> Show SavedCredentials
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SavedCredentials] -> ShowS
$cshowList :: [SavedCredentials] -> ShowS
show :: SavedCredentials -> String
$cshow :: SavedCredentials -> String
showsPrec :: I32 -> SavedCredentials -> ShowS
$cshowsPrec :: I32 -> SavedCredentials -> ShowS
Show, SavedCredentials -> SavedCredentials -> Bool
(SavedCredentials -> SavedCredentials -> Bool)
-> (SavedCredentials -> SavedCredentials -> Bool)
-> Eq SavedCredentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SavedCredentials -> SavedCredentials -> Bool
$c/= :: SavedCredentials -> SavedCredentials -> Bool
== :: SavedCredentials -> SavedCredentials -> Bool
$c== :: SavedCredentials -> SavedCredentials -> Bool
Eq, (forall x. SavedCredentials -> Rep SavedCredentials x)
-> (forall x. Rep SavedCredentials x -> SavedCredentials)
-> Generic SavedCredentials
forall x. Rep SavedCredentials x -> SavedCredentials
forall x. SavedCredentials -> Rep SavedCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SavedCredentials x -> SavedCredentials
$cfrom :: forall x. SavedCredentials -> Rep SavedCredentials x
Generic)
-- | Contains information about the payment method chosen by the user
data InputCredentials
  = -- | Applies if a user chooses some previously saved payment credentials. To use their previously saved credentials, the user must have a valid temporary password 
  InputCredentialsSaved
    { -- | Identifier of the saved credentials
      InputCredentials -> T
saved_credentials_id_1 :: T
    }
  | -- | Applies if a user enters new credentials on a payment provider website 
  InputCredentialsNew
    { -- | Contains JSON-encoded data with a credential identifier from the payment provider 
      InputCredentials -> T
data_2 :: T,
      -- | True, if the credential identifier can be saved on the server side
      InputCredentials -> Bool
allow_save_2 :: Bool
    }
  | -- | Applies if a user enters new credentials using Android Pay 
  InputCredentialsAndroidPay
    { -- | JSON-encoded data with the credential identifier
      InputCredentials -> T
data_3 :: T
    }
  | -- | Applies if a user enters new credentials using Apple Pay 
  InputCredentialsApplePay
    { -- | JSON-encoded data with the credential identifier
      InputCredentials -> T
data_4 :: T
    }
  deriving (I32 -> InputCredentials -> ShowS
[InputCredentials] -> ShowS
InputCredentials -> String
(I32 -> InputCredentials -> ShowS)
-> (InputCredentials -> String)
-> ([InputCredentials] -> ShowS)
-> Show InputCredentials
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputCredentials] -> ShowS
$cshowList :: [InputCredentials] -> ShowS
show :: InputCredentials -> String
$cshow :: InputCredentials -> String
showsPrec :: I32 -> InputCredentials -> ShowS
$cshowsPrec :: I32 -> InputCredentials -> ShowS
Show, InputCredentials -> InputCredentials -> Bool
(InputCredentials -> InputCredentials -> Bool)
-> (InputCredentials -> InputCredentials -> Bool)
-> Eq InputCredentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputCredentials -> InputCredentials -> Bool
$c/= :: InputCredentials -> InputCredentials -> Bool
== :: InputCredentials -> InputCredentials -> Bool
$c== :: InputCredentials -> InputCredentials -> Bool
Eq, (forall x. InputCredentials -> Rep InputCredentials x)
-> (forall x. Rep InputCredentials x -> InputCredentials)
-> Generic InputCredentials
forall x. Rep InputCredentials x -> InputCredentials
forall x. InputCredentials -> Rep InputCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputCredentials x -> InputCredentials
$cfrom :: forall x. InputCredentials -> Rep InputCredentials x
Generic)
data PaymentsProviderStripe
  = -- | Stripe payment provider 
  PaymentsProviderStripe
    { -- | Stripe API publishable key 
      PaymentsProviderStripe -> T
publishable_key_1 :: T,
      -- | True, if the user country must be provided 
      PaymentsProviderStripe -> Bool
need_country_1 :: Bool,
      -- | True, if the user ZIP/postal code must be provided 
      PaymentsProviderStripe -> Bool
need_postal_code_1 :: Bool,
      -- | True, if the cardholder name must be provided
      PaymentsProviderStripe -> Bool
need_cardholder_name_1 :: Bool
    }
  deriving (I32 -> PaymentsProviderStripe -> ShowS
[PaymentsProviderStripe] -> ShowS
PaymentsProviderStripe -> String
(I32 -> PaymentsProviderStripe -> ShowS)
-> (PaymentsProviderStripe -> String)
-> ([PaymentsProviderStripe] -> ShowS)
-> Show PaymentsProviderStripe
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentsProviderStripe] -> ShowS
$cshowList :: [PaymentsProviderStripe] -> ShowS
show :: PaymentsProviderStripe -> String
$cshow :: PaymentsProviderStripe -> String
showsPrec :: I32 -> PaymentsProviderStripe -> ShowS
$cshowsPrec :: I32 -> PaymentsProviderStripe -> ShowS
Show, PaymentsProviderStripe -> PaymentsProviderStripe -> Bool
(PaymentsProviderStripe -> PaymentsProviderStripe -> Bool)
-> (PaymentsProviderStripe -> PaymentsProviderStripe -> Bool)
-> Eq PaymentsProviderStripe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentsProviderStripe -> PaymentsProviderStripe -> Bool
$c/= :: PaymentsProviderStripe -> PaymentsProviderStripe -> Bool
== :: PaymentsProviderStripe -> PaymentsProviderStripe -> Bool
$c== :: PaymentsProviderStripe -> PaymentsProviderStripe -> Bool
Eq, (forall x. PaymentsProviderStripe -> Rep PaymentsProviderStripe x)
-> (forall x.
    Rep PaymentsProviderStripe x -> PaymentsProviderStripe)
-> Generic PaymentsProviderStripe
forall x. Rep PaymentsProviderStripe x -> PaymentsProviderStripe
forall x. PaymentsProviderStripe -> Rep PaymentsProviderStripe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaymentsProviderStripe x -> PaymentsProviderStripe
$cfrom :: forall x. PaymentsProviderStripe -> Rep PaymentsProviderStripe x
Generic)
data PaymentForm
  = -- | Contains information about an invoice payment form 
  PaymentForm
    { -- | Full information of the invoice 
      PaymentForm -> Invoice
invoice_1 :: Invoice,
      -- | Payment form URL 
      PaymentForm -> T
url_1 :: T,
      -- | Contains information about the payment provider, if available, to support it natively without the need for opening the URL; may be null
      PaymentForm -> PaymentsProviderStripe
payments_provider_1 :: PaymentsProviderStripe,
      -- | Saved server-side order information; may be null 
      PaymentForm -> OrderInfo
saved_order_info_1 :: OrderInfo,
      -- | Contains information about saved card credentials; may be null 
      PaymentForm -> SavedCredentials
saved_credentials_1 :: SavedCredentials,
      -- | True, if the user can choose to save credentials 
      PaymentForm -> Bool
can_save_credentials_1 :: Bool,
      -- | True, if the user will be able to save credentials protected by a password they set up
      PaymentForm -> Bool
need_password_1 :: Bool
    }
  deriving (I32 -> PaymentForm -> ShowS
[PaymentForm] -> ShowS
PaymentForm -> String
(I32 -> PaymentForm -> ShowS)
-> (PaymentForm -> String)
-> ([PaymentForm] -> ShowS)
-> Show PaymentForm
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentForm] -> ShowS
$cshowList :: [PaymentForm] -> ShowS
show :: PaymentForm -> String
$cshow :: PaymentForm -> String
showsPrec :: I32 -> PaymentForm -> ShowS
$cshowsPrec :: I32 -> PaymentForm -> ShowS
Show, PaymentForm -> PaymentForm -> Bool
(PaymentForm -> PaymentForm -> Bool)
-> (PaymentForm -> PaymentForm -> Bool) -> Eq PaymentForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentForm -> PaymentForm -> Bool
$c/= :: PaymentForm -> PaymentForm -> Bool
== :: PaymentForm -> PaymentForm -> Bool
$c== :: PaymentForm -> PaymentForm -> Bool
Eq, (forall x. PaymentForm -> Rep PaymentForm x)
-> (forall x. Rep PaymentForm x -> PaymentForm)
-> Generic PaymentForm
forall x. Rep PaymentForm x -> PaymentForm
forall x. PaymentForm -> Rep PaymentForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaymentForm x -> PaymentForm
$cfrom :: forall x. PaymentForm -> Rep PaymentForm x
Generic)
data ValidatedOrderInfo
  = -- | Contains a temporary identifier of validated order information, which is stored for one hour. Also contains the available shipping options 
  ValidatedOrderInfo
    { -- | Temporary identifier of the order information 
      ValidatedOrderInfo -> T
order_info_id_1 :: T,
      -- | Available shipping options
      ValidatedOrderInfo -> [ShippingOption]
shipping_options_1 :: ([]) (ShippingOption)
    }
  deriving (I32 -> ValidatedOrderInfo -> ShowS
[ValidatedOrderInfo] -> ShowS
ValidatedOrderInfo -> String
(I32 -> ValidatedOrderInfo -> ShowS)
-> (ValidatedOrderInfo -> String)
-> ([ValidatedOrderInfo] -> ShowS)
-> Show ValidatedOrderInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidatedOrderInfo] -> ShowS
$cshowList :: [ValidatedOrderInfo] -> ShowS
show :: ValidatedOrderInfo -> String
$cshow :: ValidatedOrderInfo -> String
showsPrec :: I32 -> ValidatedOrderInfo -> ShowS
$cshowsPrec :: I32 -> ValidatedOrderInfo -> ShowS
Show, ValidatedOrderInfo -> ValidatedOrderInfo -> Bool
(ValidatedOrderInfo -> ValidatedOrderInfo -> Bool)
-> (ValidatedOrderInfo -> ValidatedOrderInfo -> Bool)
-> Eq ValidatedOrderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidatedOrderInfo -> ValidatedOrderInfo -> Bool
$c/= :: ValidatedOrderInfo -> ValidatedOrderInfo -> Bool
== :: ValidatedOrderInfo -> ValidatedOrderInfo -> Bool
$c== :: ValidatedOrderInfo -> ValidatedOrderInfo -> Bool
Eq, (forall x. ValidatedOrderInfo -> Rep ValidatedOrderInfo x)
-> (forall x. Rep ValidatedOrderInfo x -> ValidatedOrderInfo)
-> Generic ValidatedOrderInfo
forall x. Rep ValidatedOrderInfo x -> ValidatedOrderInfo
forall x. ValidatedOrderInfo -> Rep ValidatedOrderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidatedOrderInfo x -> ValidatedOrderInfo
$cfrom :: forall x. ValidatedOrderInfo -> Rep ValidatedOrderInfo x
Generic)
data PaymentResult
  = -- | Contains the result of a payment request 
  PaymentResult
    { -- | True, if the payment request was successful; otherwise the verification_url will be not empty 
      PaymentResult -> Bool
success_1 :: Bool,
      -- | URL for additional payment credentials verification
      PaymentResult -> T
verification_url_1 :: T
    }
  deriving (I32 -> PaymentResult -> ShowS
[PaymentResult] -> ShowS
PaymentResult -> String
(I32 -> PaymentResult -> ShowS)
-> (PaymentResult -> String)
-> ([PaymentResult] -> ShowS)
-> Show PaymentResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentResult] -> ShowS
$cshowList :: [PaymentResult] -> ShowS
show :: PaymentResult -> String
$cshow :: PaymentResult -> String
showsPrec :: I32 -> PaymentResult -> ShowS
$cshowsPrec :: I32 -> PaymentResult -> ShowS
Show, PaymentResult -> PaymentResult -> Bool
(PaymentResult -> PaymentResult -> Bool)
-> (PaymentResult -> PaymentResult -> Bool) -> Eq PaymentResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentResult -> PaymentResult -> Bool
$c/= :: PaymentResult -> PaymentResult -> Bool
== :: PaymentResult -> PaymentResult -> Bool
$c== :: PaymentResult -> PaymentResult -> Bool
Eq, (forall x. PaymentResult -> Rep PaymentResult x)
-> (forall x. Rep PaymentResult x -> PaymentResult)
-> Generic PaymentResult
forall x. Rep PaymentResult x -> PaymentResult
forall x. PaymentResult -> Rep PaymentResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaymentResult x -> PaymentResult
$cfrom :: forall x. PaymentResult -> Rep PaymentResult x
Generic)
data PaymentReceipt
  = -- | Contains information about a successful payment 
  PaymentReceipt
    { -- | Point in time (Unix timestamp) when the payment was made 
      PaymentReceipt -> I32
date_1 :: I32,
      -- | User identifier of the payment provider bot 
      PaymentReceipt -> I32
payments_provider_user_id_1 :: I32,
      -- | Contains information about the invoice
      PaymentReceipt -> Invoice
invoice_1 :: Invoice,
      -- | Contains order information; may be null 
      PaymentReceipt -> OrderInfo
order_info_1 :: OrderInfo,
      -- | Chosen shipping option; may be null 
      PaymentReceipt -> ShippingOption
shipping_option_1 :: ShippingOption,
      -- | Title of the saved credentials
      PaymentReceipt -> T
credentials_title_1 :: T
    }
  deriving (I32 -> PaymentReceipt -> ShowS
[PaymentReceipt] -> ShowS
PaymentReceipt -> String
(I32 -> PaymentReceipt -> ShowS)
-> (PaymentReceipt -> String)
-> ([PaymentReceipt] -> ShowS)
-> Show PaymentReceipt
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PaymentReceipt] -> ShowS
$cshowList :: [PaymentReceipt] -> ShowS
show :: PaymentReceipt -> String
$cshow :: PaymentReceipt -> String
showsPrec :: I32 -> PaymentReceipt -> ShowS
$cshowsPrec :: I32 -> PaymentReceipt -> ShowS
Show, PaymentReceipt -> PaymentReceipt -> Bool
(PaymentReceipt -> PaymentReceipt -> Bool)
-> (PaymentReceipt -> PaymentReceipt -> Bool) -> Eq PaymentReceipt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PaymentReceipt -> PaymentReceipt -> Bool
$c/= :: PaymentReceipt -> PaymentReceipt -> Bool
== :: PaymentReceipt -> PaymentReceipt -> Bool
$c== :: PaymentReceipt -> PaymentReceipt -> Bool
Eq, (forall x. PaymentReceipt -> Rep PaymentReceipt x)
-> (forall x. Rep PaymentReceipt x -> PaymentReceipt)
-> Generic PaymentReceipt
forall x. Rep PaymentReceipt x -> PaymentReceipt
forall x. PaymentReceipt -> Rep PaymentReceipt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PaymentReceipt x -> PaymentReceipt
$cfrom :: forall x. PaymentReceipt -> Rep PaymentReceipt x
Generic)
data DatedFile
  = -- | File with the date it was uploaded 
  DatedFile
    { -- | The file 
      DatedFile -> File
file_1 :: File,
      -- | Point in time (Unix timestamp) when the file was uploaded
      DatedFile -> I32
date_1 :: I32
    }
  deriving (I32 -> DatedFile -> ShowS
[DatedFile] -> ShowS
DatedFile -> String
(I32 -> DatedFile -> ShowS)
-> (DatedFile -> String)
-> ([DatedFile] -> ShowS)
-> Show DatedFile
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatedFile] -> ShowS
$cshowList :: [DatedFile] -> ShowS
show :: DatedFile -> String
$cshow :: DatedFile -> String
showsPrec :: I32 -> DatedFile -> ShowS
$cshowsPrec :: I32 -> DatedFile -> ShowS
Show, DatedFile -> DatedFile -> Bool
(DatedFile -> DatedFile -> Bool)
-> (DatedFile -> DatedFile -> Bool) -> Eq DatedFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatedFile -> DatedFile -> Bool
$c/= :: DatedFile -> DatedFile -> Bool
== :: DatedFile -> DatedFile -> Bool
$c== :: DatedFile -> DatedFile -> Bool
Eq, (forall x. DatedFile -> Rep DatedFile x)
-> (forall x. Rep DatedFile x -> DatedFile) -> Generic DatedFile
forall x. Rep DatedFile x -> DatedFile
forall x. DatedFile -> Rep DatedFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatedFile x -> DatedFile
$cfrom :: forall x. DatedFile -> Rep DatedFile x
Generic)
-- | Contains the type of a Telegram Passport element
data PassportElementType
  = -- | A Telegram Passport element containing the user's personal details
  PassportElementTypePersonalDetails
    { 
    }
  | -- | A Telegram Passport element containing the user's passport
  PassportElementTypePassport
    { 
    }
  | -- | A Telegram Passport element containing the user's driver license
  PassportElementTypeDriverLicense
    { 
    }
  | -- | A Telegram Passport element containing the user's identity card
  PassportElementTypeIdentityCard
    { 
    }
  | -- | A Telegram Passport element containing the user's internal passport
  PassportElementTypeInternalPassport
    { 
    }
  | -- | A Telegram Passport element containing the user's address
  PassportElementTypeAddress
    { 
    }
  | -- | A Telegram Passport element containing the user's utility bill
  PassportElementTypeUtilityBill
    { 
    }
  | -- | A Telegram Passport element containing the user's bank statement
  PassportElementTypeBankStatement
    { 
    }
  | -- | A Telegram Passport element containing the user's rental agreement
  PassportElementTypeRentalAgreement
    { 
    }
  | -- | A Telegram Passport element containing the registration page of the user's passport
  PassportElementTypePassportRegistration
    { 
    }
  | -- | A Telegram Passport element containing the user's temporary registration
  PassportElementTypeTemporaryRegistration
    { 
    }
  | -- | A Telegram Passport element containing the user's phone number
  PassportElementTypePhoneNumber
    { 
    }
  | -- | A Telegram Passport element containing the user's email address
  PassportElementTypeEmailAddress
    { 
    }
  deriving (I32 -> PassportElementType -> ShowS
[PassportElementType] -> ShowS
PassportElementType -> String
(I32 -> PassportElementType -> ShowS)
-> (PassportElementType -> String)
-> ([PassportElementType] -> ShowS)
-> Show PassportElementType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementType] -> ShowS
$cshowList :: [PassportElementType] -> ShowS
show :: PassportElementType -> String
$cshow :: PassportElementType -> String
showsPrec :: I32 -> PassportElementType -> ShowS
$cshowsPrec :: I32 -> PassportElementType -> ShowS
Show, PassportElementType -> PassportElementType -> Bool
(PassportElementType -> PassportElementType -> Bool)
-> (PassportElementType -> PassportElementType -> Bool)
-> Eq PassportElementType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElementType -> PassportElementType -> Bool
$c/= :: PassportElementType -> PassportElementType -> Bool
== :: PassportElementType -> PassportElementType -> Bool
$c== :: PassportElementType -> PassportElementType -> Bool
Eq, (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)
data Date
  = -- | Represents a date according to the Gregorian calendar 
  Date
    { -- | Day of the month, 1-31 
      Date -> I32
day_1 :: I32,
      -- | Month, 1-12 
      Date -> I32
month_1 :: I32,
      -- | Year, 1-9999
      Date -> I32
year_1 :: I32
    }
  deriving (I32 -> Date -> ShowS
[Date] -> ShowS
Date -> String
(I32 -> Date -> ShowS)
-> (Date -> String) -> ([Date] -> ShowS) -> Show Date
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Date] -> ShowS
$cshowList :: [Date] -> ShowS
show :: Date -> String
$cshow :: Date -> String
showsPrec :: I32 -> Date -> ShowS
$cshowsPrec :: I32 -> Date -> ShowS
Show, Date -> Date -> Bool
(Date -> Date -> Bool) -> (Date -> Date -> Bool) -> Eq Date
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Date -> Date -> Bool
$c/= :: Date -> Date -> Bool
== :: Date -> Date -> Bool
$c== :: Date -> Date -> Bool
Eq, (forall x. Date -> Rep Date x)
-> (forall x. Rep Date x -> Date) -> Generic Date
forall x. Rep Date x -> Date
forall x. Date -> Rep Date x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Date x -> Date
$cfrom :: forall x. Date -> Rep Date x
Generic)
data PersonalDetails
  = -- | Contains the user's personal details
  PersonalDetails
    { -- | First name of the user written in English; 1-255 characters 
      PersonalDetails -> T
first_name_1 :: T,
      -- | Middle name of the user written in English; 0-255 characters 
      PersonalDetails -> T
middle_name_1 :: T,
      -- | Last name of the user written in English; 1-255 characters
      PersonalDetails -> T
last_name_1 :: T,
      -- | Native first name of the user; 1-255 characters 
      PersonalDetails -> T
native_first_name_1 :: T,
      -- | Native middle name of the user; 0-255 characters 
      PersonalDetails -> T
native_middle_name_1 :: T,
      -- | Native last name of the user; 1-255 characters
      PersonalDetails -> T
native_last_name_1 :: T,
      -- | Birthdate of the user 
      PersonalDetails -> Date
birthdate_1 :: Date,
      -- | Gender of the user, "male" or "female" 
      PersonalDetails -> T
gender_1 :: T,
      -- | A two-letter ISO 3166-1 alpha-2 country code of the user's country 
      PersonalDetails -> T
country_code_1 :: T,
      -- | A two-letter ISO 3166-1 alpha-2 country code of the user's residence country
      PersonalDetails -> T
residence_country_code_1 :: T
    }
  deriving (I32 -> PersonalDetails -> ShowS
[PersonalDetails] -> ShowS
PersonalDetails -> String
(I32 -> PersonalDetails -> ShowS)
-> (PersonalDetails -> String)
-> ([PersonalDetails] -> ShowS)
-> Show PersonalDetails
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersonalDetails] -> ShowS
$cshowList :: [PersonalDetails] -> ShowS
show :: PersonalDetails -> String
$cshow :: PersonalDetails -> String
showsPrec :: I32 -> PersonalDetails -> ShowS
$cshowsPrec :: I32 -> PersonalDetails -> ShowS
Show, PersonalDetails -> PersonalDetails -> Bool
(PersonalDetails -> PersonalDetails -> Bool)
-> (PersonalDetails -> PersonalDetails -> Bool)
-> Eq PersonalDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersonalDetails -> PersonalDetails -> Bool
$c/= :: PersonalDetails -> PersonalDetails -> Bool
== :: PersonalDetails -> PersonalDetails -> Bool
$c== :: PersonalDetails -> PersonalDetails -> Bool
Eq, (forall x. PersonalDetails -> Rep PersonalDetails x)
-> (forall x. Rep PersonalDetails x -> PersonalDetails)
-> Generic PersonalDetails
forall x. Rep PersonalDetails x -> PersonalDetails
forall x. PersonalDetails -> Rep PersonalDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PersonalDetails x -> PersonalDetails
$cfrom :: forall x. PersonalDetails -> Rep PersonalDetails x
Generic)
data IdentityDocument
  = -- | An identity document 
  IdentityDocument
    { -- | Document number; 1-24 characters 
      IdentityDocument -> T
number_1 :: T,
      -- | Document expiry date; may be null 
      IdentityDocument -> Date
expiry_date_1 :: Date,
      -- | Front side of the document
      IdentityDocument -> DatedFile
front_side_1 :: DatedFile,
      -- | Reverse side of the document; only for driver license and identity card 
      IdentityDocument -> DatedFile
reverse_side_1 :: DatedFile,
      -- | Selfie with the document; may be null 
      IdentityDocument -> DatedFile
selfie_1 :: DatedFile,
      -- | List of files containing a certified English translation of the document
      IdentityDocument -> [DatedFile]
translation_1 :: ([]) (DatedFile)
    }
  deriving (I32 -> IdentityDocument -> ShowS
[IdentityDocument] -> ShowS
IdentityDocument -> String
(I32 -> IdentityDocument -> ShowS)
-> (IdentityDocument -> String)
-> ([IdentityDocument] -> ShowS)
-> Show IdentityDocument
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [IdentityDocument] -> ShowS
$cshowList :: [IdentityDocument] -> ShowS
show :: IdentityDocument -> String
$cshow :: IdentityDocument -> String
showsPrec :: I32 -> IdentityDocument -> ShowS
$cshowsPrec :: I32 -> IdentityDocument -> ShowS
Show, IdentityDocument -> IdentityDocument -> Bool
(IdentityDocument -> IdentityDocument -> Bool)
-> (IdentityDocument -> IdentityDocument -> Bool)
-> Eq IdentityDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IdentityDocument -> IdentityDocument -> Bool
$c/= :: IdentityDocument -> IdentityDocument -> Bool
== :: IdentityDocument -> IdentityDocument -> Bool
$c== :: IdentityDocument -> IdentityDocument -> Bool
Eq, (forall x. IdentityDocument -> Rep IdentityDocument x)
-> (forall x. Rep IdentityDocument x -> IdentityDocument)
-> Generic IdentityDocument
forall x. Rep IdentityDocument x -> IdentityDocument
forall x. IdentityDocument -> Rep IdentityDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep IdentityDocument x -> IdentityDocument
$cfrom :: forall x. IdentityDocument -> Rep IdentityDocument x
Generic)
data InputIdentityDocument
  = -- | An identity document to be saved to Telegram Passport 
  InputIdentityDocument
    { -- | Document number; 1-24 characters 
      InputIdentityDocument -> T
number_1 :: T,
      -- | Document expiry date, if available 
      InputIdentityDocument -> Date
expiry_date_1 :: Date,
      -- | Front side of the document
      InputIdentityDocument -> InputFile
front_side_1 :: InputFile,
      -- | Reverse side of the document; only for driver license and identity card 
      InputIdentityDocument -> InputFile
reverse_side_1 :: InputFile,
      -- | Selfie with the document, if available 
      InputIdentityDocument -> InputFile
selfie_1 :: InputFile,
      -- | List of files containing a certified English translation of the document
      InputIdentityDocument -> [InputFile]
translation_1 :: ([]) (InputFile)
    }
  deriving (I32 -> InputIdentityDocument -> ShowS
[InputIdentityDocument] -> ShowS
InputIdentityDocument -> String
(I32 -> InputIdentityDocument -> ShowS)
-> (InputIdentityDocument -> String)
-> ([InputIdentityDocument] -> ShowS)
-> Show InputIdentityDocument
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputIdentityDocument] -> ShowS
$cshowList :: [InputIdentityDocument] -> ShowS
show :: InputIdentityDocument -> String
$cshow :: InputIdentityDocument -> String
showsPrec :: I32 -> InputIdentityDocument -> ShowS
$cshowsPrec :: I32 -> InputIdentityDocument -> ShowS
Show, InputIdentityDocument -> InputIdentityDocument -> Bool
(InputIdentityDocument -> InputIdentityDocument -> Bool)
-> (InputIdentityDocument -> InputIdentityDocument -> Bool)
-> Eq InputIdentityDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputIdentityDocument -> InputIdentityDocument -> Bool
$c/= :: InputIdentityDocument -> InputIdentityDocument -> Bool
== :: InputIdentityDocument -> InputIdentityDocument -> Bool
$c== :: InputIdentityDocument -> InputIdentityDocument -> Bool
Eq, (forall x. InputIdentityDocument -> Rep InputIdentityDocument x)
-> (forall x. Rep InputIdentityDocument x -> InputIdentityDocument)
-> Generic InputIdentityDocument
forall x. Rep InputIdentityDocument x -> InputIdentityDocument
forall x. InputIdentityDocument -> Rep InputIdentityDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputIdentityDocument x -> InputIdentityDocument
$cfrom :: forall x. InputIdentityDocument -> Rep InputIdentityDocument x
Generic)
data PersonalDocument
  = -- | A personal document, containing some information about a user 
  PersonalDocument
    { -- | List of files containing the pages of the document 
      PersonalDocument -> [DatedFile]
files_1 :: ([]) (DatedFile),
      -- | List of files containing a certified English translation of the document
      PersonalDocument -> [DatedFile]
translation_1 :: ([]) (DatedFile)
    }
  deriving (I32 -> PersonalDocument -> ShowS
[PersonalDocument] -> ShowS
PersonalDocument -> String
(I32 -> PersonalDocument -> ShowS)
-> (PersonalDocument -> String)
-> ([PersonalDocument] -> ShowS)
-> Show PersonalDocument
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PersonalDocument] -> ShowS
$cshowList :: [PersonalDocument] -> ShowS
show :: PersonalDocument -> String
$cshow :: PersonalDocument -> String
showsPrec :: I32 -> PersonalDocument -> ShowS
$cshowsPrec :: I32 -> PersonalDocument -> ShowS
Show, PersonalDocument -> PersonalDocument -> Bool
(PersonalDocument -> PersonalDocument -> Bool)
-> (PersonalDocument -> PersonalDocument -> Bool)
-> Eq PersonalDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PersonalDocument -> PersonalDocument -> Bool
$c/= :: PersonalDocument -> PersonalDocument -> Bool
== :: PersonalDocument -> PersonalDocument -> Bool
$c== :: PersonalDocument -> PersonalDocument -> Bool
Eq, (forall x. PersonalDocument -> Rep PersonalDocument x)
-> (forall x. Rep PersonalDocument x -> PersonalDocument)
-> Generic PersonalDocument
forall x. Rep PersonalDocument x -> PersonalDocument
forall x. PersonalDocument -> Rep PersonalDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PersonalDocument x -> PersonalDocument
$cfrom :: forall x. PersonalDocument -> Rep PersonalDocument x
Generic)
data InputPersonalDocument
  = -- | A personal document to be saved to Telegram Passport 
  InputPersonalDocument
    { -- | List of files containing the pages of the document 
      InputPersonalDocument -> [InputFile]
files_1 :: ([]) (InputFile),
      -- | List of files containing a certified English translation of the document
      InputPersonalDocument -> [InputFile]
translation_1 :: ([]) (InputFile)
    }
  deriving (I32 -> InputPersonalDocument -> ShowS
[InputPersonalDocument] -> ShowS
InputPersonalDocument -> String
(I32 -> InputPersonalDocument -> ShowS)
-> (InputPersonalDocument -> String)
-> ([InputPersonalDocument] -> ShowS)
-> Show InputPersonalDocument
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputPersonalDocument] -> ShowS
$cshowList :: [InputPersonalDocument] -> ShowS
show :: InputPersonalDocument -> String
$cshow :: InputPersonalDocument -> String
showsPrec :: I32 -> InputPersonalDocument -> ShowS
$cshowsPrec :: I32 -> InputPersonalDocument -> ShowS
Show, InputPersonalDocument -> InputPersonalDocument -> Bool
(InputPersonalDocument -> InputPersonalDocument -> Bool)
-> (InputPersonalDocument -> InputPersonalDocument -> Bool)
-> Eq InputPersonalDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputPersonalDocument -> InputPersonalDocument -> Bool
$c/= :: InputPersonalDocument -> InputPersonalDocument -> Bool
== :: InputPersonalDocument -> InputPersonalDocument -> Bool
$c== :: InputPersonalDocument -> InputPersonalDocument -> Bool
Eq, (forall x. InputPersonalDocument -> Rep InputPersonalDocument x)
-> (forall x. Rep InputPersonalDocument x -> InputPersonalDocument)
-> Generic InputPersonalDocument
forall x. Rep InputPersonalDocument x -> InputPersonalDocument
forall x. InputPersonalDocument -> Rep InputPersonalDocument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputPersonalDocument x -> InputPersonalDocument
$cfrom :: forall x. InputPersonalDocument -> Rep InputPersonalDocument x
Generic)
-- | Contains information about a Telegram Passport element
data PassportElement
  = -- | A Telegram Passport element containing the user's personal details 
  PassportElementPersonalDetails
    { -- | Personal details of the user
      PassportElement -> PersonalDetails
personal_details_1 :: PersonalDetails
    }
  | -- | A Telegram Passport element containing the user's passport 
  PassportElementPassport
    { -- | Passport
      PassportElement -> IdentityDocument
passport_2 :: IdentityDocument
    }
  | -- | A Telegram Passport element containing the user's driver license 
  PassportElementDriverLicense
    { -- | Driver license
      PassportElement -> IdentityDocument
driver_license_3 :: IdentityDocument
    }
  | -- | A Telegram Passport element containing the user's identity card 
  PassportElementIdentityCard
    { -- | Identity card
      PassportElement -> IdentityDocument
identity_card_4 :: IdentityDocument
    }
  | -- | A Telegram Passport element containing the user's internal passport 
  PassportElementInternalPassport
    { -- | Internal passport
      PassportElement -> IdentityDocument
internal_passport_5 :: IdentityDocument
    }
  | -- | A Telegram Passport element containing the user's address 
  PassportElementAddress
    { -- | Address
      PassportElement -> Address
address_6 :: Address
    }
  | -- | A Telegram Passport element containing the user's utility bill 
  PassportElementUtilityBill
    { -- | Utility bill
      PassportElement -> PersonalDocument
utility_bill_7 :: PersonalDocument
    }
  | -- | A Telegram Passport element containing the user's bank statement 
  PassportElementBankStatement
    { -- | Bank statement
      PassportElement -> PersonalDocument
bank_statement_8 :: PersonalDocument
    }
  | -- | A Telegram Passport element containing the user's rental agreement 
  PassportElementRentalAgreement
    { -- | Rental agreement
      PassportElement -> PersonalDocument
rental_agreement_9 :: PersonalDocument
    }
  | -- | A Telegram Passport element containing the user's passport registration pages 
  PassportElementPassportRegistration
    { -- | Passport registration pages
      PassportElement -> PersonalDocument
passport_registration_10 :: PersonalDocument
    }
  | -- | A Telegram Passport element containing the user's temporary registration 
  PassportElementTemporaryRegistration
    { -- | Temporary registration
      PassportElement -> PersonalDocument
temporary_registration_11 :: PersonalDocument
    }
  | -- | A Telegram Passport element containing the user's phone number 
  PassportElementPhoneNumber
    { -- | Phone number
      PassportElement -> T
phone_number_12 :: T
    }
  | -- | A Telegram Passport element containing the user's email address 
  PassportElementEmailAddress
    { -- | Email address
      PassportElement -> T
email_address_13 :: T
    }
  deriving (I32 -> PassportElement -> ShowS
[PassportElement] -> ShowS
PassportElement -> String
(I32 -> PassportElement -> ShowS)
-> (PassportElement -> String)
-> ([PassportElement] -> ShowS)
-> Show PassportElement
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElement] -> ShowS
$cshowList :: [PassportElement] -> ShowS
show :: PassportElement -> String
$cshow :: PassportElement -> String
showsPrec :: I32 -> PassportElement -> ShowS
$cshowsPrec :: I32 -> PassportElement -> ShowS
Show, PassportElement -> PassportElement -> Bool
(PassportElement -> PassportElement -> Bool)
-> (PassportElement -> PassportElement -> Bool)
-> Eq PassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElement -> PassportElement -> Bool
$c/= :: PassportElement -> PassportElement -> Bool
== :: PassportElement -> PassportElement -> Bool
$c== :: PassportElement -> PassportElement -> Bool
Eq, (forall x. PassportElement -> Rep PassportElement x)
-> (forall x. Rep PassportElement x -> PassportElement)
-> Generic PassportElement
forall x. Rep PassportElement x -> PassportElement
forall x. PassportElement -> Rep PassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportElement x -> PassportElement
$cfrom :: forall x. PassportElement -> Rep PassportElement x
Generic)
-- | Contains information about a Telegram Passport element to be saved
data InputPassportElement
  = -- | A Telegram Passport element to be saved containing the user's personal details 
  InputPassportElementPersonalDetails
    { -- | Personal details of the user
      InputPassportElement -> PersonalDetails
personal_details_1 :: PersonalDetails
    }
  | -- | A Telegram Passport element to be saved containing the user's passport 
  InputPassportElementPassport
    { -- | The passport to be saved
      InputPassportElement -> InputIdentityDocument
passport_2 :: InputIdentityDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's driver license 
  InputPassportElementDriverLicense
    { -- | The driver license to be saved
      InputPassportElement -> InputIdentityDocument
driver_license_3 :: InputIdentityDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's identity card 
  InputPassportElementIdentityCard
    { -- | The identity card to be saved
      InputPassportElement -> InputIdentityDocument
identity_card_4 :: InputIdentityDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's internal passport 
  InputPassportElementInternalPassport
    { -- | The internal passport to be saved
      InputPassportElement -> InputIdentityDocument
internal_passport_5 :: InputIdentityDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's address 
  InputPassportElementAddress
    { -- | The address to be saved
      InputPassportElement -> Address
address_6 :: Address
    }
  | -- | A Telegram Passport element to be saved containing the user's utility bill 
  InputPassportElementUtilityBill
    { -- | The utility bill to be saved
      InputPassportElement -> InputPersonalDocument
utility_bill_7 :: InputPersonalDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's bank statement 
  InputPassportElementBankStatement
    { -- | The bank statement to be saved
      InputPassportElement -> InputPersonalDocument
bank_statement_8 :: InputPersonalDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's rental agreement 
  InputPassportElementRentalAgreement
    { -- | The rental agreement to be saved
      InputPassportElement -> InputPersonalDocument
rental_agreement_9 :: InputPersonalDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's passport registration 
  InputPassportElementPassportRegistration
    { -- | The passport registration page to be saved
      InputPassportElement -> InputPersonalDocument
passport_registration_10 :: InputPersonalDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's temporary registration 
  InputPassportElementTemporaryRegistration
    { -- | The temporary registration document to be saved
      InputPassportElement -> InputPersonalDocument
temporary_registration_11 :: InputPersonalDocument
    }
  | -- | A Telegram Passport element to be saved containing the user's phone number 
  InputPassportElementPhoneNumber
    { -- | The phone number to be saved
      InputPassportElement -> T
phone_number_12 :: T
    }
  | -- | A Telegram Passport element to be saved containing the user's email address 
  InputPassportElementEmailAddress
    { -- | The email address to be saved
      InputPassportElement -> T
email_address_13 :: T
    }
  deriving (I32 -> InputPassportElement -> ShowS
[InputPassportElement] -> ShowS
InputPassportElement -> String
(I32 -> InputPassportElement -> ShowS)
-> (InputPassportElement -> String)
-> ([InputPassportElement] -> ShowS)
-> Show InputPassportElement
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputPassportElement] -> ShowS
$cshowList :: [InputPassportElement] -> ShowS
show :: InputPassportElement -> String
$cshow :: InputPassportElement -> String
showsPrec :: I32 -> InputPassportElement -> ShowS
$cshowsPrec :: I32 -> InputPassportElement -> ShowS
Show, InputPassportElement -> InputPassportElement -> Bool
(InputPassportElement -> InputPassportElement -> Bool)
-> (InputPassportElement -> InputPassportElement -> Bool)
-> Eq InputPassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputPassportElement -> InputPassportElement -> Bool
$c/= :: InputPassportElement -> InputPassportElement -> Bool
== :: InputPassportElement -> InputPassportElement -> Bool
$c== :: InputPassportElement -> InputPassportElement -> Bool
Eq, (forall x. InputPassportElement -> Rep InputPassportElement x)
-> (forall x. Rep InputPassportElement x -> InputPassportElement)
-> Generic InputPassportElement
forall x. Rep InputPassportElement x -> InputPassportElement
forall x. InputPassportElement -> Rep InputPassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputPassportElement x -> InputPassportElement
$cfrom :: forall x. InputPassportElement -> Rep InputPassportElement x
Generic)
data PassportElements
  = -- | Contains information about saved Telegram Passport elements 
  PassportElements
    { -- | Telegram Passport elements
      PassportElements -> [PassportElement]
elements_1 :: ([]) (PassportElement)
    }
  deriving (I32 -> PassportElements -> ShowS
[PassportElements] -> ShowS
PassportElements -> String
(I32 -> PassportElements -> ShowS)
-> (PassportElements -> String)
-> ([PassportElements] -> ShowS)
-> Show PassportElements
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElements] -> ShowS
$cshowList :: [PassportElements] -> ShowS
show :: PassportElements -> String
$cshow :: PassportElements -> String
showsPrec :: I32 -> PassportElements -> ShowS
$cshowsPrec :: I32 -> PassportElements -> ShowS
Show, PassportElements -> PassportElements -> Bool
(PassportElements -> PassportElements -> Bool)
-> (PassportElements -> PassportElements -> Bool)
-> Eq PassportElements
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElements -> PassportElements -> Bool
$c/= :: PassportElements -> PassportElements -> Bool
== :: PassportElements -> PassportElements -> Bool
$c== :: PassportElements -> PassportElements -> Bool
Eq, (forall x. PassportElements -> Rep PassportElements x)
-> (forall x. Rep PassportElements x -> PassportElements)
-> Generic PassportElements
forall x. Rep PassportElements x -> PassportElements
forall x. PassportElements -> Rep PassportElements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportElements x -> PassportElements
$cfrom :: forall x. PassportElements -> Rep PassportElements x
Generic)
-- | Contains the description of an error in a Telegram Passport element
data PassportElementErrorSource
  = -- | The element contains an error in an unspecified place. The error will be considered resolved when new data is added
  PassportElementErrorSourceUnspecified
    { 
    }
  | -- | One of the data fields contains an error. The error will be considered resolved when the value of the field changes 
  PassportElementErrorSourceDataField
    { -- | Field name
      PassportElementErrorSource -> T
field_name_2 :: T
    }
  | -- | The front side of the document contains an error. The error will be considered resolved when the file with the front side changes
  PassportElementErrorSourceFrontSide
    { 
    }
  | -- | The reverse side of the document contains an error. The error will be considered resolved when the file with the reverse side changes
  PassportElementErrorSourceReverseSide
    { 
    }
  | -- | The selfie with the document contains an error. The error will be considered resolved when the file with the selfie changes
  PassportElementErrorSourceSelfie
    { 
    }
  | -- | One of files with the translation of the document contains an error. The error will be considered resolved when the file changes 
  PassportElementErrorSourceTranslationFile
    { -- | Index of a file with the error
      PassportElementErrorSource -> I32
file_index_6 :: I32
    }
  | -- | The translation of the document contains an error. The error will be considered resolved when the list of translation files changes
  PassportElementErrorSourceTranslationFiles
    { 
    }
  | -- | The file contains an error. The error will be considered resolved when the file changes 
  PassportElementErrorSourceFile
    { -- | Index of a file with the error
      PassportElementErrorSource -> I32
file_index_8 :: I32
    }
  | -- | The list of attached files contains an error. The error will be considered resolved when the list of files changes
  PassportElementErrorSourceFiles
    { 
    }
  deriving (I32 -> PassportElementErrorSource -> ShowS
[PassportElementErrorSource] -> ShowS
PassportElementErrorSource -> String
(I32 -> PassportElementErrorSource -> ShowS)
-> (PassportElementErrorSource -> String)
-> ([PassportElementErrorSource] -> ShowS)
-> Show PassportElementErrorSource
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementErrorSource] -> ShowS
$cshowList :: [PassportElementErrorSource] -> ShowS
show :: PassportElementErrorSource -> String
$cshow :: PassportElementErrorSource -> String
showsPrec :: I32 -> PassportElementErrorSource -> ShowS
$cshowsPrec :: I32 -> PassportElementErrorSource -> ShowS
Show, PassportElementErrorSource -> PassportElementErrorSource -> Bool
(PassportElementErrorSource -> PassportElementErrorSource -> Bool)
-> (PassportElementErrorSource
    -> PassportElementErrorSource -> Bool)
-> Eq PassportElementErrorSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElementErrorSource -> PassportElementErrorSource -> Bool
$c/= :: PassportElementErrorSource -> PassportElementErrorSource -> Bool
== :: PassportElementErrorSource -> PassportElementErrorSource -> Bool
$c== :: PassportElementErrorSource -> PassportElementErrorSource -> Bool
Eq, (forall x.
 PassportElementErrorSource -> Rep PassportElementErrorSource x)
-> (forall x.
    Rep PassportElementErrorSource x -> PassportElementErrorSource)
-> Generic PassportElementErrorSource
forall x.
Rep PassportElementErrorSource x -> PassportElementErrorSource
forall x.
PassportElementErrorSource -> Rep PassportElementErrorSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PassportElementErrorSource x -> PassportElementErrorSource
$cfrom :: forall x.
PassportElementErrorSource -> Rep PassportElementErrorSource x
Generic)
data PassportElementError
  = -- | Contains the description of an error in a Telegram Passport element 
  PassportElementError
    { -- | Type of the Telegram Passport element which has the error 
      PassportElementError -> PassportElementType
type_1 :: PassportElementType,
      -- | Error message 
      PassportElementError -> T
message_1 :: T,
      -- | Error source
      PassportElementError -> PassportElementErrorSource
source_1 :: PassportElementErrorSource
    }
  deriving (I32 -> PassportElementError -> ShowS
[PassportElementError] -> ShowS
PassportElementError -> String
(I32 -> PassportElementError -> ShowS)
-> (PassportElementError -> String)
-> ([PassportElementError] -> ShowS)
-> Show PassportElementError
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementError] -> ShowS
$cshowList :: [PassportElementError] -> ShowS
show :: PassportElementError -> String
$cshow :: PassportElementError -> String
showsPrec :: I32 -> PassportElementError -> ShowS
$cshowsPrec :: I32 -> PassportElementError -> ShowS
Show, PassportElementError -> PassportElementError -> Bool
(PassportElementError -> PassportElementError -> Bool)
-> (PassportElementError -> PassportElementError -> Bool)
-> Eq PassportElementError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElementError -> PassportElementError -> Bool
$c/= :: PassportElementError -> PassportElementError -> Bool
== :: PassportElementError -> PassportElementError -> Bool
$c== :: PassportElementError -> PassportElementError -> Bool
Eq, (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)
data PassportSuitableElement
  = -- | Contains information about a Telegram Passport element that was requested by a service 
  PassportSuitableElement
    { -- | Type of the element 
      PassportSuitableElement -> PassportElementType
type_1 :: PassportElementType,
      -- | True, if a selfie is required with the identity document
      PassportSuitableElement -> Bool
is_selfie_required_1 :: Bool,
      -- | True, if a certified English translation is required with the document 
      PassportSuitableElement -> Bool
is_translation_required_1 :: Bool,
      -- | True, if personal details must include the user's name in the language of their country of residence
      PassportSuitableElement -> Bool
is_native_name_required_1 :: Bool
    }
  deriving (I32 -> PassportSuitableElement -> ShowS
[PassportSuitableElement] -> ShowS
PassportSuitableElement -> String
(I32 -> PassportSuitableElement -> ShowS)
-> (PassportSuitableElement -> String)
-> ([PassportSuitableElement] -> ShowS)
-> Show PassportSuitableElement
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportSuitableElement] -> ShowS
$cshowList :: [PassportSuitableElement] -> ShowS
show :: PassportSuitableElement -> String
$cshow :: PassportSuitableElement -> String
showsPrec :: I32 -> PassportSuitableElement -> ShowS
$cshowsPrec :: I32 -> PassportSuitableElement -> ShowS
Show, PassportSuitableElement -> PassportSuitableElement -> Bool
(PassportSuitableElement -> PassportSuitableElement -> Bool)
-> (PassportSuitableElement -> PassportSuitableElement -> Bool)
-> Eq PassportSuitableElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportSuitableElement -> PassportSuitableElement -> Bool
$c/= :: PassportSuitableElement -> PassportSuitableElement -> Bool
== :: PassportSuitableElement -> PassportSuitableElement -> Bool
$c== :: PassportSuitableElement -> PassportSuitableElement -> Bool
Eq, (forall x.
 PassportSuitableElement -> Rep PassportSuitableElement x)
-> (forall x.
    Rep PassportSuitableElement x -> PassportSuitableElement)
-> Generic PassportSuitableElement
forall x. Rep PassportSuitableElement x -> PassportSuitableElement
forall x. PassportSuitableElement -> Rep PassportSuitableElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportSuitableElement x -> PassportSuitableElement
$cfrom :: forall x. PassportSuitableElement -> Rep PassportSuitableElement x
Generic)
data PassportRequiredElement
  = -- | Contains a description of the required Telegram Passport element that was requested by a service 
  PassportRequiredElement
    { -- | List of Telegram Passport elements any of which is enough to provide
      PassportRequiredElement -> [PassportSuitableElement]
suitable_elements_1 :: ([]) (PassportSuitableElement)
    }
  deriving (I32 -> PassportRequiredElement -> ShowS
[PassportRequiredElement] -> ShowS
PassportRequiredElement -> String
(I32 -> PassportRequiredElement -> ShowS)
-> (PassportRequiredElement -> String)
-> ([PassportRequiredElement] -> ShowS)
-> Show PassportRequiredElement
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportRequiredElement] -> ShowS
$cshowList :: [PassportRequiredElement] -> ShowS
show :: PassportRequiredElement -> String
$cshow :: PassportRequiredElement -> String
showsPrec :: I32 -> PassportRequiredElement -> ShowS
$cshowsPrec :: I32 -> PassportRequiredElement -> ShowS
Show, PassportRequiredElement -> PassportRequiredElement -> Bool
(PassportRequiredElement -> PassportRequiredElement -> Bool)
-> (PassportRequiredElement -> PassportRequiredElement -> Bool)
-> Eq PassportRequiredElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportRequiredElement -> PassportRequiredElement -> Bool
$c/= :: PassportRequiredElement -> PassportRequiredElement -> Bool
== :: PassportRequiredElement -> PassportRequiredElement -> Bool
$c== :: PassportRequiredElement -> PassportRequiredElement -> Bool
Eq, (forall x.
 PassportRequiredElement -> Rep PassportRequiredElement x)
-> (forall x.
    Rep PassportRequiredElement x -> PassportRequiredElement)
-> Generic PassportRequiredElement
forall x. Rep PassportRequiredElement x -> PassportRequiredElement
forall x. PassportRequiredElement -> Rep PassportRequiredElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PassportRequiredElement x -> PassportRequiredElement
$cfrom :: forall x. PassportRequiredElement -> Rep PassportRequiredElement x
Generic)
data PassportAuthorizationForm
  = -- | Contains information about a Telegram Passport authorization form that was requested 
  PassportAuthorizationForm
    { -- | Unique identifier of the authorization form
      PassportAuthorizationForm -> I32
id_1 :: I32,
      -- | Information about the Telegram Passport elements that need to be provided to complete the form
      PassportAuthorizationForm -> [PassportRequiredElement]
required_elements_1 :: ([]) (PassportRequiredElement),
      -- | URL for the privacy policy of the service; may be empty
      PassportAuthorizationForm -> T
privacy_policy_url_1 :: T
    }
  deriving (I32 -> PassportAuthorizationForm -> ShowS
[PassportAuthorizationForm] -> ShowS
PassportAuthorizationForm -> String
(I32 -> PassportAuthorizationForm -> ShowS)
-> (PassportAuthorizationForm -> String)
-> ([PassportAuthorizationForm] -> ShowS)
-> Show PassportAuthorizationForm
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportAuthorizationForm] -> ShowS
$cshowList :: [PassportAuthorizationForm] -> ShowS
show :: PassportAuthorizationForm -> String
$cshow :: PassportAuthorizationForm -> String
showsPrec :: I32 -> PassportAuthorizationForm -> ShowS
$cshowsPrec :: I32 -> PassportAuthorizationForm -> ShowS
Show, PassportAuthorizationForm -> PassportAuthorizationForm -> Bool
(PassportAuthorizationForm -> PassportAuthorizationForm -> Bool)
-> (PassportAuthorizationForm -> PassportAuthorizationForm -> Bool)
-> Eq PassportAuthorizationForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportAuthorizationForm -> PassportAuthorizationForm -> Bool
$c/= :: PassportAuthorizationForm -> PassportAuthorizationForm -> Bool
== :: PassportAuthorizationForm -> PassportAuthorizationForm -> Bool
$c== :: PassportAuthorizationForm -> PassportAuthorizationForm -> Bool
Eq, (forall x.
 PassportAuthorizationForm -> Rep PassportAuthorizationForm x)
-> (forall x.
    Rep PassportAuthorizationForm x -> PassportAuthorizationForm)
-> Generic PassportAuthorizationForm
forall x.
Rep PassportAuthorizationForm x -> PassportAuthorizationForm
forall x.
PassportAuthorizationForm -> Rep PassportAuthorizationForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PassportAuthorizationForm x -> PassportAuthorizationForm
$cfrom :: forall x.
PassportAuthorizationForm -> Rep PassportAuthorizationForm x
Generic)
data PassportElementsWithErrors
  = -- | Contains information about a Telegram Passport elements and corresponding errors 
  PassportElementsWithErrors
    { -- | Telegram Passport elements 
      PassportElementsWithErrors -> [PassportElement]
elements_1 :: ([]) (PassportElement),
      -- | Errors in the elements that are already available
      PassportElementsWithErrors -> [PassportElementError]
errors_1 :: ([]) (PassportElementError)
    }
  deriving (I32 -> PassportElementsWithErrors -> ShowS
[PassportElementsWithErrors] -> ShowS
PassportElementsWithErrors -> String
(I32 -> PassportElementsWithErrors -> ShowS)
-> (PassportElementsWithErrors -> String)
-> ([PassportElementsWithErrors] -> ShowS)
-> Show PassportElementsWithErrors
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PassportElementsWithErrors] -> ShowS
$cshowList :: [PassportElementsWithErrors] -> ShowS
show :: PassportElementsWithErrors -> String
$cshow :: PassportElementsWithErrors -> String
showsPrec :: I32 -> PassportElementsWithErrors -> ShowS
$cshowsPrec :: I32 -> PassportElementsWithErrors -> ShowS
Show, PassportElementsWithErrors -> PassportElementsWithErrors -> Bool
(PassportElementsWithErrors -> PassportElementsWithErrors -> Bool)
-> (PassportElementsWithErrors
    -> PassportElementsWithErrors -> Bool)
-> Eq PassportElementsWithErrors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PassportElementsWithErrors -> PassportElementsWithErrors -> Bool
$c/= :: PassportElementsWithErrors -> PassportElementsWithErrors -> Bool
== :: PassportElementsWithErrors -> PassportElementsWithErrors -> Bool
$c== :: PassportElementsWithErrors -> PassportElementsWithErrors -> Bool
Eq, (forall x.
 PassportElementsWithErrors -> Rep PassportElementsWithErrors x)
-> (forall x.
    Rep PassportElementsWithErrors x -> PassportElementsWithErrors)
-> Generic PassportElementsWithErrors
forall x.
Rep PassportElementsWithErrors x -> PassportElementsWithErrors
forall x.
PassportElementsWithErrors -> Rep PassportElementsWithErrors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PassportElementsWithErrors x -> PassportElementsWithErrors
$cfrom :: forall x.
PassportElementsWithErrors -> Rep PassportElementsWithErrors x
Generic)
data EncryptedCredentials
  = -- | Contains encrypted Telegram Passport data credentials 
  EncryptedCredentials
    { -- | The encrypted credentials 
      EncryptedCredentials -> ByteString64
data_1 :: ByteString64,
      -- | The decrypted data hash 
      EncryptedCredentials -> ByteString64
hash_1 :: ByteString64,
      -- | Secret for data decryption, encrypted with the service's public key
      EncryptedCredentials -> ByteString64
secret_1 :: ByteString64
    }
  deriving (I32 -> EncryptedCredentials -> ShowS
[EncryptedCredentials] -> ShowS
EncryptedCredentials -> String
(I32 -> EncryptedCredentials -> ShowS)
-> (EncryptedCredentials -> String)
-> ([EncryptedCredentials] -> ShowS)
-> Show EncryptedCredentials
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncryptedCredentials] -> ShowS
$cshowList :: [EncryptedCredentials] -> ShowS
show :: EncryptedCredentials -> String
$cshow :: EncryptedCredentials -> String
showsPrec :: I32 -> EncryptedCredentials -> ShowS
$cshowsPrec :: I32 -> EncryptedCredentials -> ShowS
Show, EncryptedCredentials -> EncryptedCredentials -> Bool
(EncryptedCredentials -> EncryptedCredentials -> Bool)
-> (EncryptedCredentials -> EncryptedCredentials -> Bool)
-> Eq EncryptedCredentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EncryptedCredentials -> EncryptedCredentials -> Bool
$c/= :: EncryptedCredentials -> EncryptedCredentials -> Bool
== :: EncryptedCredentials -> EncryptedCredentials -> Bool
$c== :: EncryptedCredentials -> EncryptedCredentials -> Bool
Eq, (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)
data EncryptedPassportElement
  = -- | Contains information about an encrypted Telegram Passport element; for bots only 
  EncryptedPassportElement
    { -- | Type of Telegram Passport element 
      EncryptedPassportElement -> PassportElementType
type_1 :: PassportElementType,
      -- | Encrypted JSON-encoded data about the user 
      EncryptedPassportElement -> ByteString64
data_1 :: ByteString64,
      -- | The front side of an identity document 
      EncryptedPassportElement -> DatedFile
front_side_1 :: DatedFile,
      -- | The reverse side of an identity document; may be null 
      EncryptedPassportElement -> DatedFile
reverse_side_1 :: DatedFile,
      -- | Selfie with the document; may be null 
      EncryptedPassportElement -> DatedFile
selfie_1 :: DatedFile,
      -- | List of files containing a certified English translation of the document 
      EncryptedPassportElement -> [DatedFile]
translation_1 :: ([]) (DatedFile),
      -- | List of attached files 
      EncryptedPassportElement -> [DatedFile]
files_1 :: ([]) (DatedFile),
      -- | Unencrypted data, phone number or email address 
      EncryptedPassportElement -> T
value_1 :: T,
      -- | Hash of the entire element
      EncryptedPassportElement -> T
hash_1 :: T
    }
  deriving (I32 -> EncryptedPassportElement -> ShowS
[EncryptedPassportElement] -> ShowS
EncryptedPassportElement -> String
(I32 -> EncryptedPassportElement -> ShowS)
-> (EncryptedPassportElement -> String)
-> ([EncryptedPassportElement] -> ShowS)
-> Show EncryptedPassportElement
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EncryptedPassportElement] -> ShowS
$cshowList :: [EncryptedPassportElement] -> ShowS
show :: EncryptedPassportElement -> String
$cshow :: EncryptedPassportElement -> String
showsPrec :: I32 -> EncryptedPassportElement -> ShowS
$cshowsPrec :: I32 -> EncryptedPassportElement -> ShowS
Show, EncryptedPassportElement -> EncryptedPassportElement -> Bool
(EncryptedPassportElement -> EncryptedPassportElement -> Bool)
-> (EncryptedPassportElement -> EncryptedPassportElement -> Bool)
-> Eq EncryptedPassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EncryptedPassportElement -> EncryptedPassportElement -> Bool
$c/= :: EncryptedPassportElement -> EncryptedPassportElement -> Bool
== :: EncryptedPassportElement -> EncryptedPassportElement -> Bool
$c== :: EncryptedPassportElement -> EncryptedPassportElement -> Bool
Eq, (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)
-- | Contains the description of an error in a Telegram Passport element; for bots only
data InputPassportElementErrorSource
  = -- | The element contains an error in an unspecified place. The error will be considered resolved when new data is added 
  InputPassportElementErrorSourceUnspecified
    { -- | Current hash of the entire element
      InputPassportElementErrorSource -> ByteString64
element_hash_1 :: ByteString64
    }
  | -- | A data field contains an error. The error is considered resolved when the field's value changes 
  InputPassportElementErrorSourceDataField
    { -- | Field name 
      InputPassportElementErrorSource -> T
field_name_2 :: T,
      -- | Current data hash
      InputPassportElementErrorSource -> ByteString64
data_hash_2 :: ByteString64
    }
  | -- | The front side of the document contains an error. The error is considered resolved when the file with the front side of the document changes 
  InputPassportElementErrorSourceFrontSide
    { -- | Current hash of the file containing the front side
      InputPassportElementErrorSource -> ByteString64
file_hash_3 :: ByteString64
    }
  | -- | The reverse side of the document contains an error. The error is considered resolved when the file with the reverse side of the document changes 
  InputPassportElementErrorSourceReverseSide
    { -- | Current hash of the file containing the reverse side
      InputPassportElementErrorSource -> ByteString64
file_hash_4 :: ByteString64
    }
  | -- | The selfie contains an error. The error is considered resolved when the file with the selfie changes 
  InputPassportElementErrorSourceSelfie
    { -- | Current hash of the file containing the selfie
      InputPassportElementErrorSource -> ByteString64
file_hash_5 :: ByteString64
    }
  | -- | One of the files containing the translation of the document contains an error. The error is considered resolved when the file with the translation changes 
  InputPassportElementErrorSourceTranslationFile
    { -- | Current hash of the file containing the translation
      InputPassportElementErrorSource -> ByteString64
file_hash_6 :: ByteString64
    }
  | -- | The translation of the document contains an error. The error is considered resolved when the list of files changes 
  InputPassportElementErrorSourceTranslationFiles
    { -- | Current hashes of all files with the translation
      InputPassportElementErrorSource -> [ByteString64]
file_hashes_7 :: ([]) (ByteString64)
    }
  | -- | The file contains an error. The error is considered resolved when the file changes 
  InputPassportElementErrorSourceFile
    { -- | Current hash of the file which has the error
      InputPassportElementErrorSource -> ByteString64
file_hash_8 :: ByteString64
    }
  | -- | The list of attached files contains an error. The error is considered resolved when the file list changes 
  InputPassportElementErrorSourceFiles
    { -- | Current hashes of all attached files
      InputPassportElementErrorSource -> [ByteString64]
file_hashes_9 :: ([]) (ByteString64)
    }
  deriving (I32 -> InputPassportElementErrorSource -> ShowS
[InputPassportElementErrorSource] -> ShowS
InputPassportElementErrorSource -> String
(I32 -> InputPassportElementErrorSource -> ShowS)
-> (InputPassportElementErrorSource -> String)
-> ([InputPassportElementErrorSource] -> ShowS)
-> Show InputPassportElementErrorSource
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputPassportElementErrorSource] -> ShowS
$cshowList :: [InputPassportElementErrorSource] -> ShowS
show :: InputPassportElementErrorSource -> String
$cshow :: InputPassportElementErrorSource -> String
showsPrec :: I32 -> InputPassportElementErrorSource -> ShowS
$cshowsPrec :: I32 -> InputPassportElementErrorSource -> ShowS
Show, InputPassportElementErrorSource
-> InputPassportElementErrorSource -> Bool
(InputPassportElementErrorSource
 -> InputPassportElementErrorSource -> Bool)
-> (InputPassportElementErrorSource
    -> InputPassportElementErrorSource -> Bool)
-> Eq InputPassportElementErrorSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputPassportElementErrorSource
-> InputPassportElementErrorSource -> Bool
$c/= :: InputPassportElementErrorSource
-> InputPassportElementErrorSource -> Bool
== :: InputPassportElementErrorSource
-> InputPassportElementErrorSource -> Bool
$c== :: InputPassportElementErrorSource
-> InputPassportElementErrorSource -> Bool
Eq, (forall x.
 InputPassportElementErrorSource
 -> Rep InputPassportElementErrorSource x)
-> (forall x.
    Rep InputPassportElementErrorSource x
    -> InputPassportElementErrorSource)
-> Generic InputPassportElementErrorSource
forall x.
Rep InputPassportElementErrorSource x
-> InputPassportElementErrorSource
forall x.
InputPassportElementErrorSource
-> Rep InputPassportElementErrorSource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InputPassportElementErrorSource x
-> InputPassportElementErrorSource
$cfrom :: forall x.
InputPassportElementErrorSource
-> Rep InputPassportElementErrorSource x
Generic)
data InputPassportElementError
  = -- | Contains the description of an error in a Telegram Passport element; for bots only 
  InputPassportElementError
    { -- | Type of Telegram Passport element that has the error 
      InputPassportElementError -> PassportElementType
type_1 :: PassportElementType,
      -- | Error message 
      InputPassportElementError -> T
message_1 :: T,
      -- | Error source
      InputPassportElementError -> InputPassportElementErrorSource
source_1 :: InputPassportElementErrorSource
    }
  deriving (I32 -> InputPassportElementError -> ShowS
[InputPassportElementError] -> ShowS
InputPassportElementError -> String
(I32 -> InputPassportElementError -> ShowS)
-> (InputPassportElementError -> String)
-> ([InputPassportElementError] -> ShowS)
-> Show InputPassportElementError
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputPassportElementError] -> ShowS
$cshowList :: [InputPassportElementError] -> ShowS
show :: InputPassportElementError -> String
$cshow :: InputPassportElementError -> String
showsPrec :: I32 -> InputPassportElementError -> ShowS
$cshowsPrec :: I32 -> InputPassportElementError -> ShowS
Show, InputPassportElementError -> InputPassportElementError -> Bool
(InputPassportElementError -> InputPassportElementError -> Bool)
-> (InputPassportElementError -> InputPassportElementError -> Bool)
-> Eq InputPassportElementError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputPassportElementError -> InputPassportElementError -> Bool
$c/= :: InputPassportElementError -> InputPassportElementError -> Bool
== :: InputPassportElementError -> InputPassportElementError -> Bool
$c== :: InputPassportElementError -> InputPassportElementError -> Bool
Eq, (forall x.
 InputPassportElementError -> Rep InputPassportElementError x)
-> (forall x.
    Rep InputPassportElementError x -> InputPassportElementError)
-> Generic InputPassportElementError
forall x.
Rep InputPassportElementError x -> InputPassportElementError
forall x.
InputPassportElementError -> Rep InputPassportElementError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep InputPassportElementError x -> InputPassportElementError
$cfrom :: forall x.
InputPassportElementError -> Rep InputPassportElementError x
Generic)
-- | Contains the content of a message
data MessageContent
  = -- | A text message 
  MessageText
    { -- | Text of the message 
      MessageContent -> FormattedText
text_1 :: FormattedText,
      -- | A preview of the web page that's mentioned in the text; may be null
      MessageContent -> WebPage
web_page_1 :: WebPage
    }
  | -- | An animation message (GIF-style). 
  MessageAnimation
    { -- | The animation description 
      MessageContent -> Animation
animation_2 :: Animation,
      -- | Animation caption 
      MessageContent -> FormattedText
caption_2 :: FormattedText,
      -- | True, if the animation thumbnail must be blurred and the animation must be shown only while tapped
      MessageContent -> Bool
is_secret_2 :: Bool
    }
  | -- | An audio message 
  MessageAudio
    { -- | The audio description 
      MessageContent -> Audio
audio_3 :: Audio,
      -- | Audio caption
      MessageContent -> FormattedText
caption_3 :: FormattedText
    }
  | -- | A document message (general file) 
  MessageDocument
    { -- | The document description 
      MessageContent -> Document
document_4 :: Document,
      -- | Document caption
      MessageContent -> FormattedText
caption_4 :: FormattedText
    }
  | -- | A photo message 
  MessagePhoto
    { -- | The photo description 
      MessageContent -> Photo
photo_5 :: Photo,
      -- | Photo caption 
      MessageContent -> FormattedText
caption_5 :: FormattedText,
      -- | True, if the photo must be blurred and must be shown only while tapped
      MessageContent -> Bool
is_secret_5 :: Bool
    }
  | -- | An expired photo message (self-destructed after TTL has elapsed)
  MessageExpiredPhoto
    { 
    }
  | -- | A sticker message 
  MessageSticker
    { -- | The sticker description
      MessageContent -> Sticker
sticker_7 :: Sticker
    }
  | -- | A video message 
  MessageVideo
    { -- | The video description 
      MessageContent -> Video
video_8 :: Video,
      -- | Video caption 
      MessageContent -> FormattedText
caption_8 :: FormattedText,
      -- | True, if the video thumbnail must be blurred and the video must be shown only while tapped
      MessageContent -> Bool
is_secret_8 :: Bool
    }
  | -- | An expired video message (self-destructed after TTL has elapsed)
  MessageExpiredVideo
    { 
    }
  | -- | A video note message 
  MessageVideoNote
    { -- | The video note description 
      MessageContent -> VideoNote
video_note_10 :: VideoNote,
      -- | True, if at least one of the recipients has viewed the video note 
      MessageContent -> Bool
is_viewed_10 :: Bool,
      -- | True, if the video note thumbnail must be blurred and the video note must be shown only while tapped
      MessageContent -> Bool
is_secret_10 :: Bool
    }
  | -- | A voice note message 
  MessageVoiceNote
    { -- | The voice note description 
      MessageContent -> VoiceNote
voice_note_11 :: VoiceNote,
      -- | Voice note caption 
      MessageContent -> FormattedText
caption_11 :: FormattedText,
      -- | True, if at least one of the recipients has listened to the voice note
      MessageContent -> Bool
is_listened_11 :: Bool
    }
  | -- | A message with a location 
  MessageLocation
    { -- | The location description 
      MessageContent -> Location
location_12 :: Location,
      -- | Time relative to the message sent date until which the location can be updated, in seconds
      MessageContent -> I32
live_period_12 :: I32,
      -- | Left time for which the location can be updated, in seconds. updateMessageContent is not sent when this field changes
      MessageContent -> I32
expires_in_12 :: I32
    }
  | -- | A message with information about a venue 
  MessageVenue
    { -- | The venue description
      MessageContent -> Venue
venue_13 :: Venue
    }
  | -- | A message with a user contact 
  MessageContact
    { -- | The contact description
      MessageContent -> Contact
contact_14 :: Contact
    }
  | -- | A dice message. The dice value is randomly generated by the server
  MessageDice
    { -- | The animated sticker with the initial dice animation; may be null if unknown. updateMessageContent will be sent when the sticker became known
      MessageContent -> Sticker
initial_state_sticker_15 :: Sticker,
      -- | The animated sticker with the final dice animation; may be null if unknown. updateMessageContent will be sent when the sticker became known
      MessageContent -> Sticker
final_state_sticker_15 :: Sticker,
      -- | Emoji on which the dice throw animation is based
      MessageContent -> T
emoji_15 :: T,
      -- | The dice value. If the value is 0, the dice don't have final state yet
      MessageContent -> I32
value_15 :: I32,
      -- | Number of frame after which a success animation like a shower of confetti needs to be shown on updateMessageSendSucceeded
      MessageContent -> I32
success_animation_frame_number_15 :: I32
    }
  | -- | A message with a game 
  MessageGame
    { -- | The game description
      MessageContent -> Game
game_16 :: Game
    }
  | -- | A message with a poll 
  MessagePoll
    { -- | The poll description
      MessageContent -> Poll
poll_17 :: Poll
    }
  | -- | A message with an invoice from a bot 
  MessageInvoice
    { -- | Product title 
      MessageContent -> T
title_18 :: T,
      -- | A message with an invoice from a bot 
      MessageContent -> T
description_18 :: T,
      -- | Product photo; may be null 
      MessageContent -> Photo
photo_18 :: Photo,
      -- | Currency for the product price 
      MessageContent -> T
currency_18 :: T,
      -- | Product total price in the minimal quantity of the currency
      MessageContent -> I32
total_amount_18 :: I53,
      -- | Unique invoice bot start_parameter. To share an invoice use the URL https://t.me/{bot_username}?start={start_parameter} 
      MessageContent -> T
start_parameter_18 :: T,
      -- | True, if the invoice is a test invoice
      MessageContent -> Bool
is_test_18 :: Bool,
      -- | True, if the shipping address should be specified 
      MessageContent -> Bool
need_shipping_address_18 :: Bool,
      -- | The identifier of the message with the receipt, after the product has been purchased
      MessageContent -> I32
receipt_message_id_18 :: I53
    }
  | -- | A message with information about an ended call 
  MessageCall
    { -- | Reason why the call was discarded 
      MessageContent -> CallDiscardReason
discard_reason_19 :: CallDiscardReason,
      -- | Call duration, in seconds
      MessageContent -> I32
duration_19 :: I32
    }
  | -- | A newly created basic group 
  MessageBasicGroupChatCreate
    { -- | Title of the basic group 
      MessageContent -> T
title_20 :: T,
      -- | User identifiers of members in the basic group
      MessageContent -> [I32]
member_user_ids_20 :: ([]) (I32)
    }
  | -- | A newly created supergroup or channel 
  MessageSupergroupChatCreate
    { -- | Title of the supergroup or channel
      MessageContent -> T
title_21 :: T
    }
  | -- | An updated chat title 
  MessageChatChangeTitle
    { -- | New chat title
      MessageContent -> T
title_22 :: T
    }
  | -- | An updated chat photo 
  MessageChatChangePhoto
    { -- | New chat photo
      MessageContent -> Photo
photo_23 :: Photo
    }
  | -- | A deleted chat photo
  MessageChatDeletePhoto
    { 
    }
  | -- | New chat members were added 
  MessageChatAddMembers
    { -- | User identifiers of the new members
      MessageContent -> [I32]
member_user_ids_25 :: ([]) (I32)
    }
  | -- | A new member joined the chat by invite link
  MessageChatJoinByLink
    { 
    }
  | -- | A chat member was deleted 
  MessageChatDeleteMember
    { -- | User identifier of the deleted chat member
      MessageContent -> I32
user_id_27 :: I32
    }
  | -- | A basic group was upgraded to a supergroup and was deactivated as the result 
  MessageChatUpgradeTo
    { -- | Identifier of the supergroup to which the basic group was upgraded
      MessageContent -> I32
supergroup_id_28 :: I32
    }
  | -- | A supergroup has been created from a basic group 
  MessageChatUpgradeFrom
    { -- | Title of the newly created supergroup 
      MessageContent -> T
title_29 :: T,
      -- | The identifier of the original basic group
      MessageContent -> I32
basic_group_id_29 :: I32
    }
  | -- | A message has been pinned 
  MessagePinMessage
    { -- | Identifier of the pinned message, can be an identifier of a deleted message or 0
      MessageContent -> I32
message_id_30 :: I53
    }
  | -- | A screenshot of a message in the chat has been taken
  MessageScreenshotTaken
    { 
    }
  | -- | The TTL (Time To Live) setting messages in a secret chat has been changed 
  MessageChatSetTtl
    { -- | New TTL
      MessageContent -> I32
ttl_32 :: I32
    }
  | -- | A non-standard action has happened in the chat 
  MessageCustomServiceAction
    { -- | Message text to be shown in the chat
      MessageContent -> T
text_33 :: T
    }
  | -- | A new high score was achieved in a game 
  MessageGameScore
    { -- | Identifier of the message with the game, can be an identifier of a deleted message 
      MessageContent -> I32
game_message_id_34 :: I53,
      -- | Identifier of the game; may be different from the games presented in the message with the game 
      MessageContent -> I64
game_id_34 :: I64,
      -- | New score
      MessageContent -> I32
score_34 :: I32
    }
  | -- | A payment has been completed 
  MessagePaymentSuccessful
    { -- | Identifier of the message with the corresponding invoice; can be an identifier of a deleted message 
      MessageContent -> I32
invoice_message_id_35 :: I53,
      -- | Currency for the price of the product 
      MessageContent -> T
currency_35 :: T,
      -- | Total price for the product, in the minimal quantity of the currency
      MessageContent -> I32
total_amount_35 :: I53
    }
  | -- | A payment has been completed; for bots only 
  MessagePaymentSuccessfulBot
    { -- | Identifier of the message with the corresponding invoice; can be an identifier of a deleted message 
      MessageContent -> I32
invoice_message_id_36 :: I53,
      -- | Currency for price of the product
      MessageContent -> T
currency_36 :: T,
      -- | Total price for the product, in the minimal quantity of the currency 
      MessageContent -> I32
total_amount_36 :: I53,
      -- | Invoice payload 
      MessageContent -> ByteString64
invoice_payload_36 :: ByteString64,
      -- | Identifier of the shipping option chosen by the user; may be empty if not applicable 
      MessageContent -> T
shipping_option_id_36 :: T,
      -- | Information about the order; may be null
      MessageContent -> OrderInfo
order_info_36 :: OrderInfo,
      -- | Telegram payment identifier 
      MessageContent -> T
telegram_payment_charge_id_36 :: T,
      -- | Provider payment identifier
      MessageContent -> T
provider_payment_charge_id_36 :: T
    }
  | -- | A contact has registered with Telegram
  MessageContactRegistered
    { 
    }
  | -- | The current user has connected a website by logging in using Telegram Login Widget on it 
  MessageWebsiteConnected
    { -- | Domain name of the connected website
      MessageContent -> T
domain_name_38 :: T
    }
  | -- | Telegram Passport data has been sent 
  MessagePassportDataSent
    { -- | List of Telegram Passport element types sent
      MessageContent -> [PassportElementType]
types_39 :: ([]) (PassportElementType)
    }
  | -- | Telegram Passport data has been received; for bots only 
  MessagePassportDataReceived
    { -- | List of received Telegram Passport elements 
      MessageContent -> [EncryptedPassportElement]
elements_40 :: ([]) (EncryptedPassportElement),
      -- | Encrypted data credentials
      MessageContent -> EncryptedCredentials
credentials_40 :: EncryptedCredentials
    }
  | -- | Message content that is not supported by the client
  MessageUnsupported
    { 
    }
  deriving (I32 -> MessageContent -> ShowS
[MessageContent] -> ShowS
MessageContent -> String
(I32 -> MessageContent -> ShowS)
-> (MessageContent -> String)
-> ([MessageContent] -> ShowS)
-> Show MessageContent
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageContent] -> ShowS
$cshowList :: [MessageContent] -> ShowS
show :: MessageContent -> String
$cshow :: MessageContent -> String
showsPrec :: I32 -> MessageContent -> ShowS
$cshowsPrec :: I32 -> MessageContent -> ShowS
Show, MessageContent -> MessageContent -> Bool
(MessageContent -> MessageContent -> Bool)
-> (MessageContent -> MessageContent -> Bool) -> Eq MessageContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageContent -> MessageContent -> Bool
$c/= :: MessageContent -> MessageContent -> Bool
== :: MessageContent -> MessageContent -> Bool
$c== :: MessageContent -> MessageContent -> Bool
Eq, (forall x. MessageContent -> Rep MessageContent x)
-> (forall x. Rep MessageContent x -> MessageContent)
-> Generic MessageContent
forall x. Rep MessageContent x -> MessageContent
forall x. MessageContent -> Rep MessageContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageContent x -> MessageContent
$cfrom :: forall x. MessageContent -> Rep MessageContent x
Generic)
-- | Represents a part of the text which must be formatted differently
data TextEntityType
  = -- | A mention of a user by their username
  TextEntityTypeMention
    { 
    }
  | -- | A hashtag text, beginning with "#"
  TextEntityTypeHashtag
    { 
    }
  | -- | A cashtag text, beginning with "$" and consisting of capital english letters (i.e. "$USD")
  TextEntityTypeCashtag
    { 
    }
  | -- | A bot command, beginning with "/". This shouldn't be highlighted if there are no bots in the chat
  TextEntityTypeBotCommand
    { 
    }
  | -- | An HTTP URL
  TextEntityTypeUrl
    { 
    }
  | -- | An email address
  TextEntityTypeEmailAddress
    { 
    }
  | -- | A phone number
  TextEntityTypePhoneNumber
    { 
    }
  | -- | A bank card number. The getBankCardInfo method can be used to get information about the bank card
  TextEntityTypeBankCardNumber
    { 
    }
  | -- | A bold text
  TextEntityTypeBold
    { 
    }
  | -- | An italic text
  TextEntityTypeItalic
    { 
    }
  | -- | An underlined text
  TextEntityTypeUnderline
    { 
    }
  | -- | A strikethrough text
  TextEntityTypeStrikethrough
    { 
    }
  | -- | Text that must be formatted as if inside a code HTML tag
  TextEntityTypeCode
    { 
    }
  | -- | Text that must be formatted as if inside a pre HTML tag
  TextEntityTypePre
    { 
    }
  | -- | Text that must be formatted as if inside pre, and code HTML tags 
  TextEntityTypePreCode
    { -- | Programming language of the code; as defined by the sender
      TextEntityType -> T
language_15 :: T
    }
  | -- | A text description shown instead of a raw URL 
  TextEntityTypeTextUrl
    { -- | HTTP or tg:// URL to be opened when the link is clicked
      TextEntityType -> T
url_16 :: T
    }
  | -- | A text shows instead of a raw mention of the user (e.g., when the user has no username) 
  TextEntityTypeMentionName
    { -- | Identifier of the mentioned user
      TextEntityType -> I32
user_id_17 :: I32
    }
  deriving (I32 -> TextEntityType -> ShowS
[TextEntityType] -> ShowS
TextEntityType -> String
(I32 -> TextEntityType -> ShowS)
-> (TextEntityType -> String)
-> ([TextEntityType] -> ShowS)
-> Show TextEntityType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextEntityType] -> ShowS
$cshowList :: [TextEntityType] -> ShowS
show :: TextEntityType -> String
$cshow :: TextEntityType -> String
showsPrec :: I32 -> TextEntityType -> ShowS
$cshowsPrec :: I32 -> TextEntityType -> ShowS
Show, TextEntityType -> TextEntityType -> Bool
(TextEntityType -> TextEntityType -> Bool)
-> (TextEntityType -> TextEntityType -> Bool) -> Eq TextEntityType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextEntityType -> TextEntityType -> Bool
$c/= :: TextEntityType -> TextEntityType -> Bool
== :: TextEntityType -> TextEntityType -> Bool
$c== :: TextEntityType -> TextEntityType -> Bool
Eq, (forall x. TextEntityType -> Rep TextEntityType x)
-> (forall x. Rep TextEntityType x -> TextEntityType)
-> Generic TextEntityType
forall x. Rep TextEntityType x -> TextEntityType
forall x. TextEntityType -> Rep TextEntityType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextEntityType x -> TextEntityType
$cfrom :: forall x. TextEntityType -> Rep TextEntityType x
Generic)
data InputThumbnail
  = -- | A thumbnail to be sent along with a file; should be in JPEG or WEBP format for stickers, and less than 200 KB in size 
  InputThumbnail
    { -- | Thumbnail file to send. Sending thumbnails by file_id is currently not supported
      InputThumbnail -> InputFile
thumbnail_1 :: InputFile,
      -- | Thumbnail width, usually shouldn't exceed 320. Use 0 if unknown 
      InputThumbnail -> I32
width_1 :: I32,
      -- | Thumbnail height, usually shouldn't exceed 320. Use 0 if unknown
      InputThumbnail -> I32
height_1 :: I32
    }
  deriving (I32 -> InputThumbnail -> ShowS
[InputThumbnail] -> ShowS
InputThumbnail -> String
(I32 -> InputThumbnail -> ShowS)
-> (InputThumbnail -> String)
-> ([InputThumbnail] -> ShowS)
-> Show InputThumbnail
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputThumbnail] -> ShowS
$cshowList :: [InputThumbnail] -> ShowS
show :: InputThumbnail -> String
$cshow :: InputThumbnail -> String
showsPrec :: I32 -> InputThumbnail -> ShowS
$cshowsPrec :: I32 -> InputThumbnail -> ShowS
Show, InputThumbnail -> InputThumbnail -> Bool
(InputThumbnail -> InputThumbnail -> Bool)
-> (InputThumbnail -> InputThumbnail -> Bool) -> Eq InputThumbnail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputThumbnail -> InputThumbnail -> Bool
$c/= :: InputThumbnail -> InputThumbnail -> Bool
== :: InputThumbnail -> InputThumbnail -> Bool
$c== :: InputThumbnail -> InputThumbnail -> Bool
Eq, (forall x. InputThumbnail -> Rep InputThumbnail x)
-> (forall x. Rep InputThumbnail x -> InputThumbnail)
-> Generic InputThumbnail
forall x. Rep InputThumbnail x -> InputThumbnail
forall x. InputThumbnail -> Rep InputThumbnail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputThumbnail x -> InputThumbnail
$cfrom :: forall x. InputThumbnail -> Rep InputThumbnail x
Generic)
-- | Contains information about the time when a scheduled message will be sent
data MessageSchedulingState
  = -- | The message will be sent at the specified date 
  MessageSchedulingStateSendAtDate
    { -- | Date the message will be sent. The date must be within 367 days in the future
      MessageSchedulingState -> I32
send_date_1 :: I32
    }
  | -- | The message will be sent when the peer will be online. Applicable to private chats only and when the exact online status of the peer is known
  MessageSchedulingStateSendWhenOnline
    { 
    }
  deriving (I32 -> MessageSchedulingState -> ShowS
[MessageSchedulingState] -> ShowS
MessageSchedulingState -> String
(I32 -> MessageSchedulingState -> ShowS)
-> (MessageSchedulingState -> String)
-> ([MessageSchedulingState] -> ShowS)
-> Show MessageSchedulingState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageSchedulingState] -> ShowS
$cshowList :: [MessageSchedulingState] -> ShowS
show :: MessageSchedulingState -> String
$cshow :: MessageSchedulingState -> String
showsPrec :: I32 -> MessageSchedulingState -> ShowS
$cshowsPrec :: I32 -> MessageSchedulingState -> ShowS
Show, MessageSchedulingState -> MessageSchedulingState -> Bool
(MessageSchedulingState -> MessageSchedulingState -> Bool)
-> (MessageSchedulingState -> MessageSchedulingState -> Bool)
-> Eq MessageSchedulingState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageSchedulingState -> MessageSchedulingState -> Bool
$c/= :: MessageSchedulingState -> MessageSchedulingState -> Bool
== :: MessageSchedulingState -> MessageSchedulingState -> Bool
$c== :: MessageSchedulingState -> MessageSchedulingState -> Bool
Eq, (forall x. MessageSchedulingState -> Rep MessageSchedulingState x)
-> (forall x.
    Rep MessageSchedulingState x -> MessageSchedulingState)
-> Generic MessageSchedulingState
forall x. Rep MessageSchedulingState x -> MessageSchedulingState
forall x. MessageSchedulingState -> Rep MessageSchedulingState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageSchedulingState x -> MessageSchedulingState
$cfrom :: forall x. MessageSchedulingState -> Rep MessageSchedulingState x
Generic)
data SendMessageOptions
  = -- | Options to be used when a message is send
  SendMessageOptions
    { -- | Pass true to disable notification for the message. Must be false if the message is sent to a secret chat
      SendMessageOptions -> Bool
disable_notification_1 :: Bool,
      -- | Pass true if the message is sent from the background
      SendMessageOptions -> Bool
from_background_1 :: Bool,
      -- | Message scheduling state. Messages sent to a secret chat, live location messages and self-destructing messages can't be scheduled
      SendMessageOptions -> MessageSchedulingState
scheduling_state_1 :: MessageSchedulingState
    }
  deriving (I32 -> SendMessageOptions -> ShowS
[SendMessageOptions] -> ShowS
SendMessageOptions -> String
(I32 -> SendMessageOptions -> ShowS)
-> (SendMessageOptions -> String)
-> ([SendMessageOptions] -> ShowS)
-> Show SendMessageOptions
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendMessageOptions] -> ShowS
$cshowList :: [SendMessageOptions] -> ShowS
show :: SendMessageOptions -> String
$cshow :: SendMessageOptions -> String
showsPrec :: I32 -> SendMessageOptions -> ShowS
$cshowsPrec :: I32 -> SendMessageOptions -> ShowS
Show, SendMessageOptions -> SendMessageOptions -> Bool
(SendMessageOptions -> SendMessageOptions -> Bool)
-> (SendMessageOptions -> SendMessageOptions -> Bool)
-> Eq SendMessageOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendMessageOptions -> SendMessageOptions -> Bool
$c/= :: SendMessageOptions -> SendMessageOptions -> Bool
== :: SendMessageOptions -> SendMessageOptions -> Bool
$c== :: SendMessageOptions -> SendMessageOptions -> Bool
Eq, (forall x. SendMessageOptions -> Rep SendMessageOptions x)
-> (forall x. Rep SendMessageOptions x -> SendMessageOptions)
-> Generic SendMessageOptions
forall x. Rep SendMessageOptions x -> SendMessageOptions
forall x. SendMessageOptions -> Rep SendMessageOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessageOptions x -> SendMessageOptions
$cfrom :: forall x. SendMessageOptions -> Rep SendMessageOptions x
Generic)
-- | The content of a message to send
data InputMessageContent
  = -- | A text message 
  InputMessageText
    { -- | Formatted text to be sent; 1-GetOption("message_text_length_max") characters. Only Bold, Italic, Underline, Strikethrough, Code, Pre, PreCode, TextUrl and MentionName entities are allowed to be specified manually
      InputMessageContent -> FormattedText
text_1 :: FormattedText,
      -- | True, if rich web page previews for URLs in the message text should be disabled 
      InputMessageContent -> Bool
disable_web_page_preview_1 :: Bool,
      -- | True, if a chat message draft should be deleted
      InputMessageContent -> Bool
clear_draft_1 :: Bool
    }
  | -- | An animation message (GIF-style). 
  InputMessageAnimation
    { -- | Animation file to be sent 
      InputMessageContent -> InputFile
animation_2 :: InputFile,
      -- | Animation thumbnail, if available 
      InputMessageContent -> InputThumbnail
thumbnail_2 :: InputThumbnail,
      -- | Duration of the animation, in seconds 
      InputMessageContent -> I32
duration_2 :: I32,
      -- | Width of the animation; may be replaced by the server 
      InputMessageContent -> I32
width_2 :: I32,
      -- | Height of the animation; may be replaced by the server 
      InputMessageContent -> I32
height_2 :: I32,
      -- | Animation caption; 0-GetOption("message_caption_length_max") characters
      InputMessageContent -> FormattedText
caption_2 :: FormattedText
    }
  | -- | An audio message 
  InputMessageAudio
    { -- | Audio file to be sent 
      InputMessageContent -> InputFile
audio_3 :: InputFile,
      -- | Thumbnail of the cover for the album, if available 
      InputMessageContent -> InputThumbnail
album_cover_thumbnail_3 :: InputThumbnail,
      -- | Duration of the audio, in seconds; may be replaced by the server 
      InputMessageContent -> I32
duration_3 :: I32,
      -- | Title of the audio; 0-64 characters; may be replaced by the server
      InputMessageContent -> T
title_3 :: T,
      -- | Performer of the audio; 0-64 characters, may be replaced by the server 
      InputMessageContent -> T
performer_3 :: T,
      -- | Audio caption; 0-GetOption("message_caption_length_max") characters
      InputMessageContent -> FormattedText
caption_3 :: FormattedText
    }
  | -- | A document message (general file) 
  InputMessageDocument
    { -- | Document to be sent 
      InputMessageContent -> InputFile
document_4 :: InputFile,
      -- | Document thumbnail, if available 
      InputMessageContent -> InputThumbnail
thumbnail_4 :: InputThumbnail,
      -- | Document caption; 0-GetOption("message_caption_length_max") characters
      InputMessageContent -> FormattedText
caption_4 :: FormattedText
    }
  | -- | A photo message 
  InputMessagePhoto
    { -- | Photo to send 
      InputMessageContent -> InputFile
photo_5 :: InputFile,
      -- | Photo thumbnail to be sent, this is sent to the other party in secret chats only 
      InputMessageContent -> InputThumbnail
thumbnail_5 :: InputThumbnail,
      -- | File identifiers of the stickers added to the photo, if applicable 
      InputMessageContent -> [I32]
added_sticker_file_ids_5 :: ([]) (I32),
      -- | Photo width 
      InputMessageContent -> I32
width_5 :: I32,
      -- | Photo height 
      InputMessageContent -> I32
height_5 :: I32,
      -- | Photo caption; 0-GetOption("message_caption_length_max") characters
      InputMessageContent -> FormattedText
caption_5 :: FormattedText,
      -- | Photo TTL (Time To Live), in seconds (0-60). A non-zero TTL can be specified only in private chats
      InputMessageContent -> I32
ttl_5 :: I32
    }
  | -- | A sticker message 
  InputMessageSticker
    { -- | Sticker to be sent 
      InputMessageContent -> InputFile
sticker_6 :: InputFile,
      -- | Sticker thumbnail, if available 
      InputMessageContent -> InputThumbnail
thumbnail_6 :: InputThumbnail,
      -- | Sticker width 
      InputMessageContent -> I32
width_6 :: I32,
      -- | Sticker height
      InputMessageContent -> I32
height_6 :: I32
    }
  | -- | A video message 
  InputMessageVideo
    { -- | Video to be sent 
      InputMessageContent -> InputFile
video_7 :: InputFile,
      -- | Video thumbnail, if available 
      InputMessageContent -> InputThumbnail
thumbnail_7 :: InputThumbnail,
      -- | File identifiers of the stickers added to the video, if applicable
      InputMessageContent -> [I32]
added_sticker_file_ids_7 :: ([]) (I32),
      -- | Duration of the video, in seconds 
      InputMessageContent -> I32
duration_7 :: I32,
      -- | Video width 
      InputMessageContent -> I32
width_7 :: I32,
      -- | Video height 
      InputMessageContent -> I32
height_7 :: I32,
      -- | True, if the video should be tried to be streamed
      InputMessageContent -> Bool
supports_streaming_7 :: Bool,
      -- | Video caption; 0-GetOption("message_caption_length_max") characters 
      InputMessageContent -> FormattedText
caption_7 :: FormattedText,
      -- | Video TTL (Time To Live), in seconds (0-60). A non-zero TTL can be specified only in private chats
      InputMessageContent -> I32
ttl_7 :: I32
    }
  | -- | A video note message 
  InputMessageVideoNote
    { -- | Video note to be sent 
      InputMessageContent -> InputFile
video_note_8 :: InputFile,
      -- | Video thumbnail, if available 
      InputMessageContent -> InputThumbnail
thumbnail_8 :: InputThumbnail,
      -- | Duration of the video, in seconds 
      InputMessageContent -> I32
duration_8 :: I32,
      -- | Video width and height; must be positive and not greater than 640
      InputMessageContent -> I32
length_8 :: I32
    }
  | -- | A voice note message 
  InputMessageVoiceNote
    { -- | Voice note to be sent 
      InputMessageContent -> InputFile
voice_note_9 :: InputFile,
      -- | Duration of the voice note, in seconds 
      InputMessageContent -> I32
duration_9 :: I32,
      -- | Waveform representation of the voice note, in 5-bit format 
      InputMessageContent -> ByteString64
waveform_9 :: ByteString64,
      -- | Voice note caption; 0-GetOption("message_caption_length_max") characters
      InputMessageContent -> FormattedText
caption_9 :: FormattedText
    }
  | -- | A message with a location 
  InputMessageLocation
    { -- | Location to be sent 
      InputMessageContent -> Location
location_10 :: Location,
      -- | Period for which the location can be updated, in seconds; should be between 60 and 86400 for a live location and 0 otherwise
      InputMessageContent -> I32
live_period_10 :: I32
    }
  | -- | A message with information about a venue 
  InputMessageVenue
    { -- | Venue to send
      InputMessageContent -> Venue
venue_11 :: Venue
    }
  | -- | A message containing a user contact 
  InputMessageContact
    { -- | Contact to send
      InputMessageContent -> Contact
contact_12 :: Contact
    }
  | -- | A dice message 
  InputMessageDice
    { -- | Emoji on which the dice throw animation is based 
      InputMessageContent -> T
emoji_13 :: T,
      -- | True, if a chat message draft should be deleted
      InputMessageContent -> Bool
clear_draft_13 :: Bool
    }
  | -- | A message with a game; not supported for channels or secret chats 
  InputMessageGame
    { -- | User identifier of the bot that owns the game 
      InputMessageContent -> I32
bot_user_id_14 :: I32,
      -- | Short name of the game
      InputMessageContent -> T
game_short_name_14 :: T
    }
  | -- | A message with an invoice; can be used only by bots and only in private chats 
  InputMessageInvoice
    { -- | Invoice 
      InputMessageContent -> Invoice
invoice_15 :: Invoice,
      -- | Product title; 1-32 characters 
      InputMessageContent -> T
title_15 :: T,
      -- | A message with an invoice; can be used only by bots and only in private chats 
      InputMessageContent -> T
description_15 :: T,
      -- | Product photo URL; optional 
      InputMessageContent -> T
photo_url_15 :: T,
      -- | Product photo size 
      InputMessageContent -> I32
photo_size_15 :: I32,
      -- | Product photo width 
      InputMessageContent -> I32
photo_width_15 :: I32,
      -- | Product photo height
      InputMessageContent -> I32
photo_height_15 :: I32,
      -- | The invoice payload 
      InputMessageContent -> ByteString64
payload_15 :: ByteString64,
      -- | Payment provider token 
      InputMessageContent -> T
provider_token_15 :: T,
      -- | JSON-encoded data about the invoice, which will be shared with the payment provider 
      InputMessageContent -> T
provider_data_15 :: T,
      -- | Unique invoice bot start_parameter for the generation of this invoice
      InputMessageContent -> T
start_parameter_15 :: T
    }
  | -- | A message with a poll. Polls can't be sent to secret chats. Polls can be sent only to a private chat with a bot 
  InputMessagePoll
    { -- | Poll question, 1-255 characters 
      InputMessageContent -> T
question_16 :: T,
      -- | List of poll answer options, 2-10 strings 1-100 characters each
      InputMessageContent -> [T]
options_16 :: ([]) (T),
      -- | True, if the poll voters are anonymous. Non-anonymous polls can't be sent or forwarded to channels 
      InputMessageContent -> Bool
is_anonymous_16 :: Bool,
      -- | Type of the poll
      InputMessageContent -> PollType
type_16 :: PollType,
      -- | Amount of time the poll will be active after creation, in seconds; for bots only
      InputMessageContent -> I32
open_period_16 :: I32,
      -- | Point in time (Unix timestamp) when the poll will be automatically closed; for bots only
      InputMessageContent -> I32
close_date_16 :: I32,
      -- | True, if the poll needs to be sent already closed; for bots only
      InputMessageContent -> Bool
is_closed_16 :: Bool
    }
  | -- | A forwarded message 
  InputMessageForwarded
    { -- | Identifier for the chat this forwarded message came from 
      InputMessageContent -> I32
from_chat_id_17 :: I53,
      -- | Identifier of the message to forward
      InputMessageContent -> I32
message_id_17 :: I53,
      -- | True, if a game message should be shared within a launched game; applies only to game messages
      InputMessageContent -> Bool
in_game_share_17 :: Bool,
      -- | True, if content of the message needs to be copied without a link to the original message. Always true if the message is forwarded to a secret chat
      InputMessageContent -> Bool
send_copy_17 :: Bool,
      -- | True, if media caption of the message copy needs to be removed. Ignored if send_copy is false
      InputMessageContent -> Bool
remove_caption_17 :: Bool
    }
  deriving (I32 -> InputMessageContent -> ShowS
[InputMessageContent] -> ShowS
InputMessageContent -> String
(I32 -> InputMessageContent -> ShowS)
-> (InputMessageContent -> String)
-> ([InputMessageContent] -> ShowS)
-> Show InputMessageContent
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputMessageContent] -> ShowS
$cshowList :: [InputMessageContent] -> ShowS
show :: InputMessageContent -> String
$cshow :: InputMessageContent -> String
showsPrec :: I32 -> InputMessageContent -> ShowS
$cshowsPrec :: I32 -> InputMessageContent -> ShowS
Show, InputMessageContent -> InputMessageContent -> Bool
(InputMessageContent -> InputMessageContent -> Bool)
-> (InputMessageContent -> InputMessageContent -> Bool)
-> Eq InputMessageContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputMessageContent -> InputMessageContent -> Bool
$c/= :: InputMessageContent -> InputMessageContent -> Bool
== :: InputMessageContent -> InputMessageContent -> Bool
$c== :: InputMessageContent -> InputMessageContent -> Bool
Eq, (forall x. InputMessageContent -> Rep InputMessageContent x)
-> (forall x. Rep InputMessageContent x -> InputMessageContent)
-> Generic InputMessageContent
forall x. Rep InputMessageContent x -> InputMessageContent
forall x. InputMessageContent -> Rep InputMessageContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputMessageContent x -> InputMessageContent
$cfrom :: forall x. InputMessageContent -> Rep InputMessageContent x
Generic)
-- | Represents a filter for message search results
data SearchMessagesFilter
  = -- | Returns all found messages, no filter is applied
  SearchMessagesFilterEmpty
    { 
    }
  | -- | Returns only animation messages
  SearchMessagesFilterAnimation
    { 
    }
  | -- | Returns only audio messages
  SearchMessagesFilterAudio
    { 
    }
  | -- | Returns only document messages
  SearchMessagesFilterDocument
    { 
    }
  | -- | Returns only photo messages
  SearchMessagesFilterPhoto
    { 
    }
  | -- | Returns only video messages
  SearchMessagesFilterVideo
    { 
    }
  | -- | Returns only voice note messages
  SearchMessagesFilterVoiceNote
    { 
    }
  | -- | Returns only photo and video messages
  SearchMessagesFilterPhotoAndVideo
    { 
    }
  | -- | Returns only messages containing URLs
  SearchMessagesFilterUrl
    { 
    }
  | -- | Returns only messages containing chat photos
  SearchMessagesFilterChatPhoto
    { 
    }
  | -- | Returns only call messages
  SearchMessagesFilterCall
    { 
    }
  | -- | Returns only incoming call messages with missed/declined discard reasons
  SearchMessagesFilterMissedCall
    { 
    }
  | -- | Returns only video note messages
  SearchMessagesFilterVideoNote
    { 
    }
  | -- | Returns only voice and video note messages
  SearchMessagesFilterVoiceAndVideoNote
    { 
    }
  | -- | Returns only messages with mentions of the current user, or messages that are replies to their messages
  SearchMessagesFilterMention
    { 
    }
  | -- | Returns only messages with unread mentions of the current user, or messages that are replies to their messages. When using this filter the results can't be additionally filtered by a query or by the sending user
  SearchMessagesFilterUnreadMention
    { 
    }
  | -- | Returns only failed to send messages. This filter can be used only if the message database is used
  SearchMessagesFilterFailedToSend
    { 
    }
  deriving (I32 -> SearchMessagesFilter -> ShowS
[SearchMessagesFilter] -> ShowS
SearchMessagesFilter -> String
(I32 -> SearchMessagesFilter -> ShowS)
-> (SearchMessagesFilter -> String)
-> ([SearchMessagesFilter] -> ShowS)
-> Show SearchMessagesFilter
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchMessagesFilter] -> ShowS
$cshowList :: [SearchMessagesFilter] -> ShowS
show :: SearchMessagesFilter -> String
$cshow :: SearchMessagesFilter -> String
showsPrec :: I32 -> SearchMessagesFilter -> ShowS
$cshowsPrec :: I32 -> SearchMessagesFilter -> ShowS
Show, SearchMessagesFilter -> SearchMessagesFilter -> Bool
(SearchMessagesFilter -> SearchMessagesFilter -> Bool)
-> (SearchMessagesFilter -> SearchMessagesFilter -> Bool)
-> Eq SearchMessagesFilter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchMessagesFilter -> SearchMessagesFilter -> Bool
$c/= :: SearchMessagesFilter -> SearchMessagesFilter -> Bool
== :: SearchMessagesFilter -> SearchMessagesFilter -> Bool
$c== :: SearchMessagesFilter -> SearchMessagesFilter -> Bool
Eq, (forall x. SearchMessagesFilter -> Rep SearchMessagesFilter x)
-> (forall x. Rep SearchMessagesFilter x -> SearchMessagesFilter)
-> Generic SearchMessagesFilter
forall x. Rep SearchMessagesFilter x -> SearchMessagesFilter
forall x. SearchMessagesFilter -> Rep SearchMessagesFilter x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchMessagesFilter x -> SearchMessagesFilter
$cfrom :: forall x. SearchMessagesFilter -> Rep SearchMessagesFilter x
Generic)
-- | Describes the different types of activity in a chat
data ChatAction
  = -- | The user is typing a message
  ChatActionTyping
    { 
    }
  | -- | The user is recording a video
  ChatActionRecordingVideo
    { 
    }
  | -- | The user is uploading a video 
  ChatActionUploadingVideo
    { -- | Upload progress, as a percentage
      ChatAction -> I32
progress_3 :: I32
    }
  | -- | The user is recording a voice note
  ChatActionRecordingVoiceNote
    { 
    }
  | -- | The user is uploading a voice note 
  ChatActionUploadingVoiceNote
    { -- | Upload progress, as a percentage
      ChatAction -> I32
progress_5 :: I32
    }
  | -- | The user is uploading a photo 
  ChatActionUploadingPhoto
    { -- | Upload progress, as a percentage
      ChatAction -> I32
progress_6 :: I32
    }
  | -- | The user is uploading a document 
  ChatActionUploadingDocument
    { -- | Upload progress, as a percentage
      ChatAction -> I32
progress_7 :: I32
    }
  | -- | The user is picking a location or venue to send
  ChatActionChoosingLocation
    { 
    }
  | -- | The user is picking a contact to send
  ChatActionChoosingContact
    { 
    }
  | -- | The user has started to play a game
  ChatActionStartPlayingGame
    { 
    }
  | -- | The user is recording a video note
  ChatActionRecordingVideoNote
    { 
    }
  | -- | The user is uploading a video note 
  ChatActionUploadingVideoNote
    { -- | Upload progress, as a percentage
      ChatAction -> I32
progress_12 :: I32
    }
  | -- | The user has cancelled the previous action
  ChatActionCancel
    { 
    }
  deriving (I32 -> ChatAction -> ShowS
[ChatAction] -> ShowS
ChatAction -> String
(I32 -> ChatAction -> ShowS)
-> (ChatAction -> String)
-> ([ChatAction] -> ShowS)
-> Show ChatAction
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatAction] -> ShowS
$cshowList :: [ChatAction] -> ShowS
show :: ChatAction -> String
$cshow :: ChatAction -> String
showsPrec :: I32 -> ChatAction -> ShowS
$cshowsPrec :: I32 -> ChatAction -> ShowS
Show, ChatAction -> ChatAction -> Bool
(ChatAction -> ChatAction -> Bool)
-> (ChatAction -> ChatAction -> Bool) -> Eq ChatAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatAction -> ChatAction -> Bool
$c/= :: ChatAction -> ChatAction -> Bool
== :: ChatAction -> ChatAction -> Bool
$c== :: ChatAction -> ChatAction -> Bool
Eq, (forall x. ChatAction -> Rep ChatAction x)
-> (forall x. Rep ChatAction x -> ChatAction) -> Generic ChatAction
forall x. Rep ChatAction x -> ChatAction
forall x. ChatAction -> Rep ChatAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatAction x -> ChatAction
$cfrom :: forall x. ChatAction -> Rep ChatAction x
Generic)
-- | Describes the last time the user was online
data UserStatus
  = -- | The user status was never changed
  UserStatusEmpty
    { 
    }
  | -- | The user is online 
  UserStatusOnline
    { -- | Point in time (Unix timestamp) when the user's online status will expire
      UserStatus -> I32
expires_2 :: I32
    }
  | -- | The user is offline 
  UserStatusOffline
    { -- | Point in time (Unix timestamp) when the user was last online
      UserStatus -> I32
was_online_3 :: I32
    }
  | -- | The user was online recently
  UserStatusRecently
    { 
    }
  | -- | The user is offline, but was online last week
  UserStatusLastWeek
    { 
    }
  | -- | The user is offline, but was online last month
  UserStatusLastMonth
    { 
    }
  deriving (I32 -> UserStatus -> ShowS
[UserStatus] -> ShowS
UserStatus -> String
(I32 -> UserStatus -> ShowS)
-> (UserStatus -> String)
-> ([UserStatus] -> ShowS)
-> Show UserStatus
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserStatus] -> ShowS
$cshowList :: [UserStatus] -> ShowS
show :: UserStatus -> String
$cshow :: UserStatus -> String
showsPrec :: I32 -> UserStatus -> ShowS
$cshowsPrec :: I32 -> UserStatus -> ShowS
Show, UserStatus -> UserStatus -> Bool
(UserStatus -> UserStatus -> Bool)
-> (UserStatus -> UserStatus -> Bool) -> Eq UserStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserStatus -> UserStatus -> Bool
$c/= :: UserStatus -> UserStatus -> Bool
== :: UserStatus -> UserStatus -> Bool
$c== :: UserStatus -> UserStatus -> Bool
Eq, (forall x. UserStatus -> Rep UserStatus x)
-> (forall x. Rep UserStatus x -> UserStatus) -> Generic UserStatus
forall x. Rep UserStatus x -> UserStatus
forall x. UserStatus -> Rep UserStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserStatus x -> UserStatus
$cfrom :: forall x. UserStatus -> Rep UserStatus x
Generic)
data Stickers
  = -- | Represents a list of stickers 
  Stickers
    { -- | List of stickers
      Stickers -> [Sticker]
stickers_1 :: ([]) (Sticker)
    }
  deriving (I32 -> Stickers -> ShowS
[Stickers] -> ShowS
Stickers -> String
(I32 -> Stickers -> ShowS)
-> (Stickers -> String) -> ([Stickers] -> ShowS) -> Show Stickers
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Stickers] -> ShowS
$cshowList :: [Stickers] -> ShowS
show :: Stickers -> String
$cshow :: Stickers -> String
showsPrec :: I32 -> Stickers -> ShowS
$cshowsPrec :: I32 -> Stickers -> ShowS
Show, Stickers -> Stickers -> Bool
(Stickers -> Stickers -> Bool)
-> (Stickers -> Stickers -> Bool) -> Eq Stickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Stickers -> Stickers -> Bool
$c/= :: Stickers -> Stickers -> Bool
== :: Stickers -> Stickers -> Bool
$c== :: Stickers -> Stickers -> Bool
Eq, (forall x. Stickers -> Rep Stickers x)
-> (forall x. Rep Stickers x -> Stickers) -> Generic Stickers
forall x. Rep Stickers x -> Stickers
forall x. Stickers -> Rep Stickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Stickers x -> Stickers
$cfrom :: forall x. Stickers -> Rep Stickers x
Generic)
data Emojis
  = -- | Represents a list of emoji 
  Emojis
    { -- | List of emojis
      Emojis -> [T]
emojis_1 :: ([]) (T)
    }
  deriving (I32 -> Emojis -> ShowS
[Emojis] -> ShowS
Emojis -> String
(I32 -> Emojis -> ShowS)
-> (Emojis -> String) -> ([Emojis] -> ShowS) -> Show Emojis
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Emojis] -> ShowS
$cshowList :: [Emojis] -> ShowS
show :: Emojis -> String
$cshow :: Emojis -> String
showsPrec :: I32 -> Emojis -> ShowS
$cshowsPrec :: I32 -> Emojis -> ShowS
Show, Emojis -> Emojis -> Bool
(Emojis -> Emojis -> Bool)
-> (Emojis -> Emojis -> Bool) -> Eq Emojis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Emojis -> Emojis -> Bool
$c/= :: Emojis -> Emojis -> Bool
== :: Emojis -> Emojis -> Bool
$c== :: Emojis -> Emojis -> Bool
Eq, (forall x. Emojis -> Rep Emojis x)
-> (forall x. Rep Emojis x -> Emojis) -> Generic Emojis
forall x. Rep Emojis x -> Emojis
forall x. Emojis -> Rep Emojis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Emojis x -> Emojis
$cfrom :: forall x. Emojis -> Rep Emojis x
Generic)
data StickerSet
  = -- | Represents a sticker set
  StickerSet
    { -- | Identifier of the sticker set 
      StickerSet -> I64
id_1 :: I64,
      -- | Title of the sticker set 
      StickerSet -> T
title_1 :: T,
      -- | Name of the sticker set 
      StickerSet -> T
name_1 :: T,
      -- | Sticker set thumbnail in WEBP format with width and height 100; may be null. The file can be downloaded only before the thumbnail is changed
      StickerSet -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | True, if the sticker set has been installed by the current user 
      StickerSet -> Bool
is_installed_1 :: Bool,
      -- | True, if the sticker set has been archived. A sticker set can't be installed and archived simultaneously
      StickerSet -> Bool
is_archived_1 :: Bool,
      -- | True, if the sticker set is official 
      StickerSet -> Bool
is_official_1 :: Bool,
      -- | True, is the stickers in the set are animated 
      StickerSet -> Bool
is_animated_1 :: Bool,
      -- | True, if the stickers in the set are masks 
      StickerSet -> Bool
is_masks_1 :: Bool,
      -- | True for already viewed trending sticker sets
      StickerSet -> Bool
is_viewed_1 :: Bool,
      -- | List of stickers in this set 
      StickerSet -> [Sticker]
stickers_1 :: ([]) (Sticker),
      -- | A list of emoji corresponding to the stickers in the same order. The list is only for informational purposes, because a sticker is always sent with a fixed emoji from the corresponding Sticker object
      StickerSet -> [Emojis]
emojis_1 :: ([]) (Emojis)
    }
  deriving (I32 -> StickerSet -> ShowS
[StickerSet] -> ShowS
StickerSet -> String
(I32 -> StickerSet -> ShowS)
-> (StickerSet -> String)
-> ([StickerSet] -> ShowS)
-> Show StickerSet
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StickerSet] -> ShowS
$cshowList :: [StickerSet] -> ShowS
show :: StickerSet -> String
$cshow :: StickerSet -> String
showsPrec :: I32 -> StickerSet -> ShowS
$cshowsPrec :: I32 -> StickerSet -> ShowS
Show, StickerSet -> StickerSet -> Bool
(StickerSet -> StickerSet -> Bool)
-> (StickerSet -> StickerSet -> Bool) -> Eq StickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StickerSet -> StickerSet -> Bool
$c/= :: StickerSet -> StickerSet -> Bool
== :: StickerSet -> StickerSet -> Bool
$c== :: StickerSet -> StickerSet -> Bool
Eq, (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)
data StickerSetInfo
  = -- | Represents short information about a sticker set
  StickerSetInfo
    { -- | Identifier of the sticker set 
      StickerSetInfo -> I64
id_1 :: I64,
      -- | Title of the sticker set 
      StickerSetInfo -> T
title_1 :: T,
      -- | Name of the sticker set 
      StickerSetInfo -> T
name_1 :: T,
      -- | Sticker set thumbnail in WEBP format with width and height 100; may be null
      StickerSetInfo -> PhotoSize
thumbnail_1 :: PhotoSize,
      -- | True, if the sticker set has been installed by current user 
      StickerSetInfo -> Bool
is_installed_1 :: Bool,
      -- | True, if the sticker set has been archived. A sticker set can't be installed and archived simultaneously
      StickerSetInfo -> Bool
is_archived_1 :: Bool,
      -- | True, if the sticker set is official 
      StickerSetInfo -> Bool
is_official_1 :: Bool,
      -- | True, is the stickers in the set are animated 
      StickerSetInfo -> Bool
is_animated_1 :: Bool,
      -- | True, if the stickers in the set are masks 
      StickerSetInfo -> Bool
is_masks_1 :: Bool,
      -- | True for already viewed trending sticker sets
      StickerSetInfo -> Bool
is_viewed_1 :: Bool,
      -- | Total number of stickers in the set 
      StickerSetInfo -> I32
size_1 :: I32,
      -- | Contains up to the first 5 stickers from the set, depending on the context. If the client needs more stickers the full set should be requested
      StickerSetInfo -> [Sticker]
covers_1 :: ([]) (Sticker)
    }
  deriving (I32 -> StickerSetInfo -> ShowS
[StickerSetInfo] -> ShowS
StickerSetInfo -> String
(I32 -> StickerSetInfo -> ShowS)
-> (StickerSetInfo -> String)
-> ([StickerSetInfo] -> ShowS)
-> Show StickerSetInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StickerSetInfo] -> ShowS
$cshowList :: [StickerSetInfo] -> ShowS
show :: StickerSetInfo -> String
$cshow :: StickerSetInfo -> String
showsPrec :: I32 -> StickerSetInfo -> ShowS
$cshowsPrec :: I32 -> StickerSetInfo -> ShowS
Show, StickerSetInfo -> StickerSetInfo -> Bool
(StickerSetInfo -> StickerSetInfo -> Bool)
-> (StickerSetInfo -> StickerSetInfo -> Bool) -> Eq StickerSetInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StickerSetInfo -> StickerSetInfo -> Bool
$c/= :: StickerSetInfo -> StickerSetInfo -> Bool
== :: StickerSetInfo -> StickerSetInfo -> Bool
$c== :: StickerSetInfo -> StickerSetInfo -> Bool
Eq, (forall x. StickerSetInfo -> Rep StickerSetInfo x)
-> (forall x. Rep StickerSetInfo x -> StickerSetInfo)
-> Generic StickerSetInfo
forall x. Rep StickerSetInfo x -> StickerSetInfo
forall x. StickerSetInfo -> Rep StickerSetInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StickerSetInfo x -> StickerSetInfo
$cfrom :: forall x. StickerSetInfo -> Rep StickerSetInfo x
Generic)
data StickerSets
  = -- | Represents a list of sticker sets 
  StickerSets
    { -- | Approximate total number of sticker sets found 
      StickerSets -> I32
total_count_1 :: I32,
      -- | List of sticker sets
      StickerSets -> [StickerSetInfo]
sets_1 :: ([]) (StickerSetInfo)
    }
  deriving (I32 -> StickerSets -> ShowS
[StickerSets] -> ShowS
StickerSets -> String
(I32 -> StickerSets -> ShowS)
-> (StickerSets -> String)
-> ([StickerSets] -> ShowS)
-> Show StickerSets
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StickerSets] -> ShowS
$cshowList :: [StickerSets] -> ShowS
show :: StickerSets -> String
$cshow :: StickerSets -> String
showsPrec :: I32 -> StickerSets -> ShowS
$cshowsPrec :: I32 -> StickerSets -> ShowS
Show, StickerSets -> StickerSets -> Bool
(StickerSets -> StickerSets -> Bool)
-> (StickerSets -> StickerSets -> Bool) -> Eq StickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StickerSets -> StickerSets -> Bool
$c/= :: StickerSets -> StickerSets -> Bool
== :: StickerSets -> StickerSets -> Bool
$c== :: StickerSets -> StickerSets -> Bool
Eq, (forall x. StickerSets -> Rep StickerSets x)
-> (forall x. Rep StickerSets x -> StickerSets)
-> Generic StickerSets
forall x. Rep StickerSets x -> StickerSets
forall x. StickerSets -> Rep StickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StickerSets x -> StickerSets
$cfrom :: forall x. StickerSets -> Rep StickerSets x
Generic)
-- | Describes the reason why a call was discarded
data CallDiscardReason
  = -- | The call wasn't discarded, or the reason is unknown
  CallDiscardReasonEmpty
    { 
    }
  | -- | The call was ended before the conversation started. It was cancelled by the caller or missed by the other party
  CallDiscardReasonMissed
    { 
    }
  | -- | The call was ended before the conversation started. It was declined by the other party
  CallDiscardReasonDeclined
    { 
    }
  | -- | The call was ended during the conversation because the users were disconnected
  CallDiscardReasonDisconnected
    { 
    }
  | -- | The call was ended because one of the parties hung up
  CallDiscardReasonHungUp
    { 
    }
  deriving (I32 -> CallDiscardReason -> ShowS
[CallDiscardReason] -> ShowS
CallDiscardReason -> String
(I32 -> CallDiscardReason -> ShowS)
-> (CallDiscardReason -> String)
-> ([CallDiscardReason] -> ShowS)
-> Show CallDiscardReason
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallDiscardReason] -> ShowS
$cshowList :: [CallDiscardReason] -> ShowS
show :: CallDiscardReason -> String
$cshow :: CallDiscardReason -> String
showsPrec :: I32 -> CallDiscardReason -> ShowS
$cshowsPrec :: I32 -> CallDiscardReason -> ShowS
Show, CallDiscardReason -> CallDiscardReason -> Bool
(CallDiscardReason -> CallDiscardReason -> Bool)
-> (CallDiscardReason -> CallDiscardReason -> Bool)
-> Eq CallDiscardReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallDiscardReason -> CallDiscardReason -> Bool
$c/= :: CallDiscardReason -> CallDiscardReason -> Bool
== :: CallDiscardReason -> CallDiscardReason -> Bool
$c== :: CallDiscardReason -> CallDiscardReason -> Bool
Eq, (forall x. CallDiscardReason -> Rep CallDiscardReason x)
-> (forall x. Rep CallDiscardReason x -> CallDiscardReason)
-> Generic CallDiscardReason
forall x. Rep CallDiscardReason x -> CallDiscardReason
forall x. CallDiscardReason -> Rep CallDiscardReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallDiscardReason x -> CallDiscardReason
$cfrom :: forall x. CallDiscardReason -> Rep CallDiscardReason x
Generic)
data CallProtocol
  = -- | Specifies the supported call protocols
  CallProtocol
    { -- | True, if UDP peer-to-peer connections are supported
      CallProtocol -> Bool
udp_p2p_1 :: Bool,
      -- | True, if connection through UDP reflectors is supported
      CallProtocol -> Bool
udp_reflector_1 :: Bool,
      -- | The minimum supported API layer; use 65
      CallProtocol -> I32
min_layer_1 :: I32,
      -- | The maximum supported API layer; use 65
      CallProtocol -> I32
max_layer_1 :: I32,
      -- | List of supported libtgvoip versions
      CallProtocol -> [T]
library_versions_1 :: ([]) (T)
    }
  deriving (I32 -> CallProtocol -> ShowS
[CallProtocol] -> ShowS
CallProtocol -> String
(I32 -> CallProtocol -> ShowS)
-> (CallProtocol -> String)
-> ([CallProtocol] -> ShowS)
-> Show CallProtocol
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallProtocol] -> ShowS
$cshowList :: [CallProtocol] -> ShowS
show :: CallProtocol -> String
$cshow :: CallProtocol -> String
showsPrec :: I32 -> CallProtocol -> ShowS
$cshowsPrec :: I32 -> CallProtocol -> ShowS
Show, CallProtocol -> CallProtocol -> Bool
(CallProtocol -> CallProtocol -> Bool)
-> (CallProtocol -> CallProtocol -> Bool) -> Eq CallProtocol
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallProtocol -> CallProtocol -> Bool
$c/= :: CallProtocol -> CallProtocol -> Bool
== :: CallProtocol -> CallProtocol -> Bool
$c== :: CallProtocol -> CallProtocol -> Bool
Eq, (forall x. CallProtocol -> Rep CallProtocol x)
-> (forall x. Rep CallProtocol x -> CallProtocol)
-> Generic CallProtocol
forall x. Rep CallProtocol x -> CallProtocol
forall x. CallProtocol -> Rep CallProtocol x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallProtocol x -> CallProtocol
$cfrom :: forall x. CallProtocol -> Rep CallProtocol x
Generic)
data CallConnection
  = -- | Describes the address of UDP reflectors 
  CallConnection
    { -- | Reflector identifier 
      CallConnection -> I64
id_1 :: I64,
      -- | IPv4 reflector address 
      CallConnection -> T
ip_1 :: T,
      -- | IPv6 reflector address 
      CallConnection -> T
ipv6_1 :: T,
      -- | Reflector port number 
      CallConnection -> I32
port_1 :: I32,
      -- | Connection peer tag
      CallConnection -> ByteString64
peer_tag_1 :: ByteString64
    }
  deriving (I32 -> CallConnection -> ShowS
[CallConnection] -> ShowS
CallConnection -> String
(I32 -> CallConnection -> ShowS)
-> (CallConnection -> String)
-> ([CallConnection] -> ShowS)
-> Show CallConnection
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallConnection] -> ShowS
$cshowList :: [CallConnection] -> ShowS
show :: CallConnection -> String
$cshow :: CallConnection -> String
showsPrec :: I32 -> CallConnection -> ShowS
$cshowsPrec :: I32 -> CallConnection -> ShowS
Show, CallConnection -> CallConnection -> Bool
(CallConnection -> CallConnection -> Bool)
-> (CallConnection -> CallConnection -> Bool) -> Eq CallConnection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallConnection -> CallConnection -> Bool
$c/= :: CallConnection -> CallConnection -> Bool
== :: CallConnection -> CallConnection -> Bool
$c== :: CallConnection -> CallConnection -> Bool
Eq, (forall x. CallConnection -> Rep CallConnection x)
-> (forall x. Rep CallConnection x -> CallConnection)
-> Generic CallConnection
forall x. Rep CallConnection x -> CallConnection
forall x. CallConnection -> Rep CallConnection x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallConnection x -> CallConnection
$cfrom :: forall x. CallConnection -> Rep CallConnection x
Generic)
data CallId
  = -- | Contains the call identifier 
  CallId
    { -- | Call identifier
      CallId -> I32
id_1 :: I32
    }
  deriving (I32 -> CallId -> ShowS
[CallId] -> ShowS
CallId -> String
(I32 -> CallId -> ShowS)
-> (CallId -> String) -> ([CallId] -> ShowS) -> Show CallId
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallId] -> ShowS
$cshowList :: [CallId] -> ShowS
show :: CallId -> String
$cshow :: CallId -> String
showsPrec :: I32 -> CallId -> ShowS
$cshowsPrec :: I32 -> CallId -> ShowS
Show, CallId -> CallId -> Bool
(CallId -> CallId -> Bool)
-> (CallId -> CallId -> Bool) -> Eq CallId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallId -> CallId -> Bool
$c/= :: CallId -> CallId -> Bool
== :: CallId -> CallId -> Bool
$c== :: CallId -> CallId -> Bool
Eq, (forall x. CallId -> Rep CallId x)
-> (forall x. Rep CallId x -> CallId) -> Generic CallId
forall x. Rep CallId x -> CallId
forall x. CallId -> Rep CallId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallId x -> CallId
$cfrom :: forall x. CallId -> Rep CallId x
Generic)
-- | Describes the current call state
data CallState
  = -- | The call is pending, waiting to be accepted by a user 
  CallStatePending
    { -- | True, if the call has already been created by the server 
      CallState -> Bool
is_created_1 :: Bool,
      -- | True, if the call has already been received by the other party
      CallState -> Bool
is_received_1 :: Bool
    }
  | -- | The call has been answered and encryption keys are being exchanged
  CallStateExchangingKeys
    { 
    }
  | -- | The call is ready to use 
  CallStateReady
    { -- | Call protocols supported by the peer 
      CallState -> CallProtocol
protocol_3 :: CallProtocol,
      -- | Available UDP reflectors 
      CallState -> [CallConnection]
connections_3 :: ([]) (CallConnection),
      -- | A JSON-encoded call config 
      CallState -> T
config_3 :: T,
      -- | Call encryption key 
      CallState -> ByteString64
encryption_key_3 :: ByteString64,
      -- | Encryption key emojis fingerprint 
      CallState -> [T]
emojis_3 :: ([]) (T),
      -- | True, if peer-to-peer connection is allowed by users privacy settings
      CallState -> Bool
allow_p2p_3 :: Bool
    }
  | -- | The call is hanging up after discardCall has been called
  CallStateHangingUp
    { 
    }
  | -- | The call has ended successfully 
  CallStateDiscarded
    { -- | The reason, why the call has ended 
      CallState -> CallDiscardReason
reason_5 :: CallDiscardReason,
      -- | True, if the call rating should be sent to the server 
      CallState -> Bool
need_rating_5 :: Bool,
      -- | True, if the call debug information should be sent to the server
      CallState -> Bool
need_debug_information_5 :: Bool
    }
  | -- | The call has ended with an error 
  CallStateError
    { -- | Error. An error with the code 4005000 will be returned if an outgoing call is missed because of an expired timeout
      CallState -> Error
error_6 :: Error
    }
  deriving (I32 -> CallState -> ShowS
[CallState] -> ShowS
CallState -> String
(I32 -> CallState -> ShowS)
-> (CallState -> String)
-> ([CallState] -> ShowS)
-> Show CallState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallState] -> ShowS
$cshowList :: [CallState] -> ShowS
show :: CallState -> String
$cshow :: CallState -> String
showsPrec :: I32 -> CallState -> ShowS
$cshowsPrec :: I32 -> CallState -> ShowS
Show, CallState -> CallState -> Bool
(CallState -> CallState -> Bool)
-> (CallState -> CallState -> Bool) -> Eq CallState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallState -> CallState -> Bool
$c/= :: CallState -> CallState -> Bool
== :: CallState -> CallState -> Bool
$c== :: CallState -> CallState -> Bool
Eq, (forall x. CallState -> Rep CallState x)
-> (forall x. Rep CallState x -> CallState) -> Generic CallState
forall x. Rep CallState x -> CallState
forall x. CallState -> Rep CallState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallState x -> CallState
$cfrom :: forall x. CallState -> Rep CallState x
Generic)
-- | Describes the exact type of a problem with a call
data CallProblem
  = -- | The user heard their own voice
  CallProblemEcho
    { 
    }
  | -- | The user heard background noise
  CallProblemNoise
    { 
    }
  | -- | The other side kept disappearing
  CallProblemInterruptions
    { 
    }
  | -- | The speech was distorted
  CallProblemDistortedSpeech
    { 
    }
  | -- | The user couldn't hear the other side
  CallProblemSilentLocal
    { 
    }
  | -- | The other side couldn't hear the user
  CallProblemSilentRemote
    { 
    }
  | -- | The call ended unexpectedly
  CallProblemDropped
    { 
    }
  deriving (I32 -> CallProblem -> ShowS
[CallProblem] -> ShowS
CallProblem -> String
(I32 -> CallProblem -> ShowS)
-> (CallProblem -> String)
-> ([CallProblem] -> ShowS)
-> Show CallProblem
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallProblem] -> ShowS
$cshowList :: [CallProblem] -> ShowS
show :: CallProblem -> String
$cshow :: CallProblem -> String
showsPrec :: I32 -> CallProblem -> ShowS
$cshowsPrec :: I32 -> CallProblem -> ShowS
Show, CallProblem -> CallProblem -> Bool
(CallProblem -> CallProblem -> Bool)
-> (CallProblem -> CallProblem -> Bool) -> Eq CallProblem
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallProblem -> CallProblem -> Bool
$c/= :: CallProblem -> CallProblem -> Bool
== :: CallProblem -> CallProblem -> Bool
$c== :: CallProblem -> CallProblem -> Bool
Eq, (forall x. CallProblem -> Rep CallProblem x)
-> (forall x. Rep CallProblem x -> CallProblem)
-> Generic CallProblem
forall x. Rep CallProblem x -> CallProblem
forall x. CallProblem -> Rep CallProblem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallProblem x -> CallProblem
$cfrom :: forall x. CallProblem -> Rep CallProblem x
Generic)
data Call
  = -- | Describes a call 
  Call
    { -- | Call identifier, not persistent 
      Call -> I32
id_1 :: I32,
      -- | Peer user identifier 
      Call -> I32
user_id_1 :: I32,
      -- | True, if the call is outgoing 
      Call -> Bool
is_outgoing_1 :: Bool,
      -- | Call state
      Call -> CallState
state_1 :: CallState
    }
  deriving (I32 -> Call -> ShowS
[Call] -> ShowS
Call -> String
(I32 -> Call -> ShowS)
-> (Call -> String) -> ([Call] -> ShowS) -> Show Call
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Call] -> ShowS
$cshowList :: [Call] -> ShowS
show :: Call -> String
$cshow :: Call -> String
showsPrec :: I32 -> Call -> ShowS
$cshowsPrec :: I32 -> Call -> ShowS
Show, Call -> Call -> Bool
(Call -> Call -> Bool) -> (Call -> Call -> Bool) -> Eq Call
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Call -> Call -> Bool
$c/= :: Call -> Call -> Bool
== :: Call -> Call -> Bool
$c== :: Call -> Call -> Bool
Eq, (forall x. Call -> Rep Call x)
-> (forall x. Rep Call x -> Call) -> Generic Call
forall x. Rep Call x -> Call
forall x. Call -> Rep Call x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Call x -> Call
$cfrom :: forall x. Call -> Rep Call x
Generic)
data PhoneNumberAuthenticationSettings
  = -- | Contains settings for the authentication of the user's phone number
  PhoneNumberAuthenticationSettings
    { -- | Pass true if the authentication code may be sent via flash call to the specified phone number
      PhoneNumberAuthenticationSettings -> Bool
allow_flash_call_1 :: Bool,
      -- | Pass true if the authenticated phone number is used on the current device
      PhoneNumberAuthenticationSettings -> Bool
is_current_phone_number_1 :: Bool,
      -- | For official applications only. True, if the app can use Android SMS Retriever API (requires Google Play Services >= 10.2) to automatically receive the authentication code from the SMS. See https://developers.google.com/identity/sms-retriever/ for more details
      PhoneNumberAuthenticationSettings -> Bool
allow_sms_retriever_api_1 :: Bool
    }
  deriving (I32 -> PhoneNumberAuthenticationSettings -> ShowS
[PhoneNumberAuthenticationSettings] -> ShowS
PhoneNumberAuthenticationSettings -> String
(I32 -> PhoneNumberAuthenticationSettings -> ShowS)
-> (PhoneNumberAuthenticationSettings -> String)
-> ([PhoneNumberAuthenticationSettings] -> ShowS)
-> Show PhoneNumberAuthenticationSettings
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PhoneNumberAuthenticationSettings] -> ShowS
$cshowList :: [PhoneNumberAuthenticationSettings] -> ShowS
show :: PhoneNumberAuthenticationSettings -> String
$cshow :: PhoneNumberAuthenticationSettings -> String
showsPrec :: I32 -> PhoneNumberAuthenticationSettings -> ShowS
$cshowsPrec :: I32 -> PhoneNumberAuthenticationSettings -> ShowS
Show, PhoneNumberAuthenticationSettings
-> PhoneNumberAuthenticationSettings -> Bool
(PhoneNumberAuthenticationSettings
 -> PhoneNumberAuthenticationSettings -> Bool)
-> (PhoneNumberAuthenticationSettings
    -> PhoneNumberAuthenticationSettings -> Bool)
-> Eq PhoneNumberAuthenticationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PhoneNumberAuthenticationSettings
-> PhoneNumberAuthenticationSettings -> Bool
$c/= :: PhoneNumberAuthenticationSettings
-> PhoneNumberAuthenticationSettings -> Bool
== :: PhoneNumberAuthenticationSettings
-> PhoneNumberAuthenticationSettings -> Bool
$c== :: PhoneNumberAuthenticationSettings
-> PhoneNumberAuthenticationSettings -> Bool
Eq, (forall x.
 PhoneNumberAuthenticationSettings
 -> Rep PhoneNumberAuthenticationSettings x)
-> (forall x.
    Rep PhoneNumberAuthenticationSettings x
    -> PhoneNumberAuthenticationSettings)
-> Generic PhoneNumberAuthenticationSettings
forall x.
Rep PhoneNumberAuthenticationSettings x
-> PhoneNumberAuthenticationSettings
forall x.
PhoneNumberAuthenticationSettings
-> Rep PhoneNumberAuthenticationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PhoneNumberAuthenticationSettings x
-> PhoneNumberAuthenticationSettings
$cfrom :: forall x.
PhoneNumberAuthenticationSettings
-> Rep PhoneNumberAuthenticationSettings x
Generic)
data Animations
  = -- | Represents a list of animations 
  Animations
    { -- | List of animations
      Animations -> [Animation]
animations_1 :: ([]) (Animation)
    }
  deriving (I32 -> Animations -> ShowS
[Animations] -> ShowS
Animations -> String
(I32 -> Animations -> ShowS)
-> (Animations -> String)
-> ([Animations] -> ShowS)
-> Show Animations
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Animations] -> ShowS
$cshowList :: [Animations] -> ShowS
show :: Animations -> String
$cshow :: Animations -> String
showsPrec :: I32 -> Animations -> ShowS
$cshowsPrec :: I32 -> Animations -> ShowS
Show, Animations -> Animations -> Bool
(Animations -> Animations -> Bool)
-> (Animations -> Animations -> Bool) -> Eq Animations
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Animations -> Animations -> Bool
$c/= :: Animations -> Animations -> Bool
== :: Animations -> Animations -> Bool
$c== :: Animations -> Animations -> Bool
Eq, (forall x. Animations -> Rep Animations x)
-> (forall x. Rep Animations x -> Animations) -> Generic Animations
forall x. Rep Animations x -> Animations
forall x. Animations -> Rep Animations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Animations x -> Animations
$cfrom :: forall x. Animations -> Rep Animations x
Generic)
data ImportedContacts
  = -- | Represents the result of an ImportContacts request 
  ImportedContacts
    { -- | User identifiers of the imported contacts in the same order as they were specified in the request; 0 if the contact is not yet a registered user
      ImportedContacts -> [I32]
user_ids_1 :: ([]) (I32),
      -- | The number of users that imported the corresponding contact; 0 for already registered users or if unavailable
      ImportedContacts -> [I32]
importer_count_1 :: ([]) (I32)
    }
  deriving (I32 -> ImportedContacts -> ShowS
[ImportedContacts] -> ShowS
ImportedContacts -> String
(I32 -> ImportedContacts -> ShowS)
-> (ImportedContacts -> String)
-> ([ImportedContacts] -> ShowS)
-> Show ImportedContacts
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportedContacts] -> ShowS
$cshowList :: [ImportedContacts] -> ShowS
show :: ImportedContacts -> String
$cshow :: ImportedContacts -> String
showsPrec :: I32 -> ImportedContacts -> ShowS
$cshowsPrec :: I32 -> ImportedContacts -> ShowS
Show, ImportedContacts -> ImportedContacts -> Bool
(ImportedContacts -> ImportedContacts -> Bool)
-> (ImportedContacts -> ImportedContacts -> Bool)
-> Eq ImportedContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportedContacts -> ImportedContacts -> Bool
$c/= :: ImportedContacts -> ImportedContacts -> Bool
== :: ImportedContacts -> ImportedContacts -> Bool
$c== :: ImportedContacts -> ImportedContacts -> Bool
Eq, (forall x. ImportedContacts -> Rep ImportedContacts x)
-> (forall x. Rep ImportedContacts x -> ImportedContacts)
-> Generic ImportedContacts
forall x. Rep ImportedContacts x -> ImportedContacts
forall x. ImportedContacts -> Rep ImportedContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportedContacts x -> ImportedContacts
$cfrom :: forall x. ImportedContacts -> Rep ImportedContacts x
Generic)
data HttpUrl
  = -- | Contains an HTTP URL 
  HttpUrl
    { -- | The URL
      HttpUrl -> T
url_1 :: T
    }
  deriving (I32 -> HttpUrl -> ShowS
[HttpUrl] -> ShowS
HttpUrl -> String
(I32 -> HttpUrl -> ShowS)
-> (HttpUrl -> String) -> ([HttpUrl] -> ShowS) -> Show HttpUrl
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HttpUrl] -> ShowS
$cshowList :: [HttpUrl] -> ShowS
show :: HttpUrl -> String
$cshow :: HttpUrl -> String
showsPrec :: I32 -> HttpUrl -> ShowS
$cshowsPrec :: I32 -> HttpUrl -> ShowS
Show, HttpUrl -> HttpUrl -> Bool
(HttpUrl -> HttpUrl -> Bool)
-> (HttpUrl -> HttpUrl -> Bool) -> Eq HttpUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HttpUrl -> HttpUrl -> Bool
$c/= :: HttpUrl -> HttpUrl -> Bool
== :: HttpUrl -> HttpUrl -> Bool
$c== :: HttpUrl -> HttpUrl -> Bool
Eq, (forall x. HttpUrl -> Rep HttpUrl x)
-> (forall x. Rep HttpUrl x -> HttpUrl) -> Generic HttpUrl
forall x. Rep HttpUrl x -> HttpUrl
forall x. HttpUrl -> Rep HttpUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HttpUrl x -> HttpUrl
$cfrom :: forall x. HttpUrl -> Rep HttpUrl x
Generic)
-- | Represents a single result of an inline query; for bots only
data InputInlineQueryResult
  = -- | Represents a link to an animated GIF or an animated (i.e. without sound) H.264/MPEG-4 AVC video
  InputInlineQueryResultAnimation
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_1 :: T,
      -- | Title of the query result
      InputInlineQueryResult -> T
title_1 :: T,
      -- | URL of the result thumbnail (JPEG, GIF, or MPEG4), if it exists 
      InputInlineQueryResult -> T
thumbnail_url_1 :: T,
      -- | MIME type of the video thumbnail. If non-empty, must be one of "image/jpeg", "image/gif" and "video/mp4"
      InputInlineQueryResult -> T
thumbnail_mime_type_1 :: T,
      -- | The URL of the video file (file size must not exceed 1MB) 
      InputInlineQueryResult -> T
video_url_1 :: T,
      -- | MIME type of the video file. Must be one of "image/gif" and "video/mp4"
      InputInlineQueryResult -> T
video_mime_type_1 :: T,
      -- | Duration of the video, in seconds 
      InputInlineQueryResult -> I32
video_duration_1 :: I32,
      -- | Width of the video 
      InputInlineQueryResult -> I32
video_width_1 :: I32,
      -- | Height of the video
      InputInlineQueryResult -> I32
video_height_1 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_1 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageAnimation, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_1 :: InputMessageContent
    }
  | -- | Represents a link to an article or web page 
  InputInlineQueryResultArticle
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_2 :: T,
      -- | URL of the result, if it exists 
      InputInlineQueryResult -> T
url_2 :: T,
      -- | True, if the URL must be not shown 
      InputInlineQueryResult -> Bool
hide_url_2 :: Bool,
      -- | Title of the result
      InputInlineQueryResult -> T
title_2 :: T,
      -- | Represents a link to an article or web page 
      InputInlineQueryResult -> T
description_2 :: T,
      -- | URL of the result thumbnail, if it exists 
      InputInlineQueryResult -> T
thumbnail_url_2 :: T,
      -- | Thumbnail width, if known 
      InputInlineQueryResult -> I32
thumbnail_width_2 :: I32,
      -- | Thumbnail height, if known
      InputInlineQueryResult -> I32
thumbnail_height_2 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_2 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_2 :: InputMessageContent
    }
  | -- | Represents a link to an MP3 audio file 
  InputInlineQueryResultAudio
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_3 :: T,
      -- | Title of the audio file 
      InputInlineQueryResult -> T
title_3 :: T,
      -- | Performer of the audio file
      InputInlineQueryResult -> T
performer_3 :: T,
      -- | The URL of the audio file 
      InputInlineQueryResult -> T
audio_url_3 :: T,
      -- | Audio file duration, in seconds
      InputInlineQueryResult -> I32
audio_duration_3 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_3 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageAudio, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_3 :: InputMessageContent
    }
  | -- | Represents a user contact 
  InputInlineQueryResultContact
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_4 :: T,
      -- | User contact 
      InputInlineQueryResult -> Contact
contact_4 :: Contact,
      -- | URL of the result thumbnail, if it exists 
      InputInlineQueryResult -> T
thumbnail_url_4 :: T,
      -- | Thumbnail width, if known 
      InputInlineQueryResult -> I32
thumbnail_width_4 :: I32,
      -- | Thumbnail height, if known
      InputInlineQueryResult -> I32
thumbnail_height_4 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_4 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_4 :: InputMessageContent
    }
  | -- | Represents a link to a file 
  InputInlineQueryResultDocument
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_5 :: T,
      -- | Title of the resulting file 
      InputInlineQueryResult -> T
title_5 :: T,
      -- | Represents a link to a file 
      InputInlineQueryResult -> T
description_5 :: T,
      -- | URL of the file 
      InputInlineQueryResult -> T
document_url_5 :: T,
      -- | MIME type of the file content; only "application/pdf" and "application/zip" are currently allowed
      InputInlineQueryResult -> T
mime_type_5 :: T,
      -- | The URL of the file thumbnail, if it exists 
      InputInlineQueryResult -> T
thumbnail_url_5 :: T,
      -- | Width of the thumbnail 
      InputInlineQueryResult -> I32
thumbnail_width_5 :: I32,
      -- | Height of the thumbnail
      InputInlineQueryResult -> I32
thumbnail_height_5 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_5 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageDocument, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_5 :: InputMessageContent
    }
  | -- | Represents a game 
  InputInlineQueryResultGame
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_6 :: T,
      -- | Short name of the game 
      InputInlineQueryResult -> T
game_short_name_6 :: T,
      -- | Message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_6 :: ReplyMarkup
    }
  | -- | Represents a point on the map 
  InputInlineQueryResultLocation
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_7 :: T,
      -- | Location result 
      InputInlineQueryResult -> Location
location_7 :: Location,
      -- | Amount of time relative to the message sent time until the location can be updated, in seconds 
      InputInlineQueryResult -> I32
live_period_7 :: I32,
      -- | Title of the result 
      InputInlineQueryResult -> T
title_7 :: T,
      -- | URL of the result thumbnail, if it exists 
      InputInlineQueryResult -> T
thumbnail_url_7 :: T,
      -- | Thumbnail width, if known 
      InputInlineQueryResult -> I32
thumbnail_width_7 :: I32,
      -- | Thumbnail height, if known
      InputInlineQueryResult -> I32
thumbnail_height_7 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_7 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_7 :: InputMessageContent
    }
  | -- | Represents link to a JPEG image 
  InputInlineQueryResultPhoto
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_8 :: T,
      -- | Title of the result, if known 
      InputInlineQueryResult -> T
title_8 :: T,
      -- | Represents link to a JPEG image 
      InputInlineQueryResult -> T
description_8 :: T,
      -- | URL of the photo thumbnail, if it exists
      InputInlineQueryResult -> T
thumbnail_url_8 :: T,
      -- | The URL of the JPEG photo (photo size must not exceed 5MB) 
      InputInlineQueryResult -> T
photo_url_8 :: T,
      -- | Width of the photo 
      InputInlineQueryResult -> I32
photo_width_8 :: I32,
      -- | Height of the photo
      InputInlineQueryResult -> I32
photo_height_8 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_8 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessagePhoto, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_8 :: InputMessageContent
    }
  | -- | Represents a link to a WEBP or TGS sticker 
  InputInlineQueryResultSticker
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_9 :: T,
      -- | URL of the sticker thumbnail, if it exists
      InputInlineQueryResult -> T
thumbnail_url_9 :: T,
      -- | The URL of the WEBP or TGS sticker (sticker file size must not exceed 5MB) 
      InputInlineQueryResult -> T
sticker_url_9 :: T,
      -- | Width of the sticker 
      InputInlineQueryResult -> I32
sticker_width_9 :: I32,
      -- | Height of the sticker
      InputInlineQueryResult -> I32
sticker_height_9 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_9 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, inputMessageSticker, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_9 :: InputMessageContent
    }
  | -- | Represents information about a venue 
  InputInlineQueryResultVenue
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_10 :: T,
      -- | Venue result 
      InputInlineQueryResult -> Venue
venue_10 :: Venue,
      -- | URL of the result thumbnail, if it exists 
      InputInlineQueryResult -> T
thumbnail_url_10 :: T,
      -- | Thumbnail width, if known 
      InputInlineQueryResult -> I32
thumbnail_width_10 :: I32,
      -- | Thumbnail height, if known
      InputInlineQueryResult -> I32
thumbnail_height_10 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_10 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_10 :: InputMessageContent
    }
  | -- | Represents a link to a page containing an embedded video player or a video file 
  InputInlineQueryResultVideo
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_11 :: T,
      -- | Title of the result 
      InputInlineQueryResult -> T
title_11 :: T,
      -- | Represents a link to a page containing an embedded video player or a video file 
      InputInlineQueryResult -> T
description_11 :: T,
      -- | The URL of the video thumbnail (JPEG), if it exists 
      InputInlineQueryResult -> T
thumbnail_url_11 :: T,
      -- | URL of the embedded video player or video file 
      InputInlineQueryResult -> T
video_url_11 :: T,
      -- | MIME type of the content of the video URL, only "text/html" or "video/mp4" are currently supported
      InputInlineQueryResult -> T
mime_type_11 :: T,
      -- | Width of the video 
      InputInlineQueryResult -> I32
video_width_11 :: I32,
      -- | Height of the video 
      InputInlineQueryResult -> I32
video_height_11 :: I32,
      -- | Video duration, in seconds
      InputInlineQueryResult -> I32
video_duration_11 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_11 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageVideo, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_11 :: InputMessageContent
    }
  | -- | Represents a link to an opus-encoded audio file within an OGG container, single channel audio 
  InputInlineQueryResultVoiceNote
    { -- | Unique identifier of the query result 
      InputInlineQueryResult -> T
id_12 :: T,
      -- | Title of the voice note
      InputInlineQueryResult -> T
title_12 :: T,
      -- | The URL of the voice note file 
      InputInlineQueryResult -> T
voice_note_url_12 :: T,
      -- | Duration of the voice note, in seconds
      InputInlineQueryResult -> I32
voice_note_duration_12 :: I32,
      -- | The message reply markup. Must be of type replyMarkupInlineKeyboard or null
      InputInlineQueryResult -> ReplyMarkup
reply_markup_12 :: ReplyMarkup,
      -- | The content of the message to be sent. Must be one of the following types: InputMessageText, InputMessageVoiceNote, InputMessageLocation, InputMessageVenue or InputMessageContact
      InputInlineQueryResult -> InputMessageContent
input_message_content_12 :: InputMessageContent
    }
  deriving (I32 -> InputInlineQueryResult -> ShowS
[InputInlineQueryResult] -> ShowS
InputInlineQueryResult -> String
(I32 -> InputInlineQueryResult -> ShowS)
-> (InputInlineQueryResult -> String)
-> ([InputInlineQueryResult] -> ShowS)
-> Show InputInlineQueryResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputInlineQueryResult] -> ShowS
$cshowList :: [InputInlineQueryResult] -> ShowS
show :: InputInlineQueryResult -> String
$cshow :: InputInlineQueryResult -> String
showsPrec :: I32 -> InputInlineQueryResult -> ShowS
$cshowsPrec :: I32 -> InputInlineQueryResult -> ShowS
Show, InputInlineQueryResult -> InputInlineQueryResult -> Bool
(InputInlineQueryResult -> InputInlineQueryResult -> Bool)
-> (InputInlineQueryResult -> InputInlineQueryResult -> Bool)
-> Eq InputInlineQueryResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputInlineQueryResult -> InputInlineQueryResult -> Bool
$c/= :: InputInlineQueryResult -> InputInlineQueryResult -> Bool
== :: InputInlineQueryResult -> InputInlineQueryResult -> Bool
$c== :: InputInlineQueryResult -> InputInlineQueryResult -> Bool
Eq, (forall x. InputInlineQueryResult -> Rep InputInlineQueryResult x)
-> (forall x.
    Rep InputInlineQueryResult x -> InputInlineQueryResult)
-> Generic InputInlineQueryResult
forall x. Rep InputInlineQueryResult x -> InputInlineQueryResult
forall x. InputInlineQueryResult -> Rep InputInlineQueryResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputInlineQueryResult x -> InputInlineQueryResult
$cfrom :: forall x. InputInlineQueryResult -> Rep InputInlineQueryResult x
Generic)
-- | Represents a single result of an inline query
data InlineQueryResult
  = -- | Represents a link to an article or web page 
  InlineQueryResultArticle
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_1 :: T,
      -- | URL of the result, if it exists 
      InlineQueryResult -> T
url_1 :: T,
      -- | True, if the URL must be not shown 
      InlineQueryResult -> Bool
hide_url_1 :: Bool,
      -- | Title of the result
      InlineQueryResult -> T
title_1 :: T,
      -- | Represents a link to an article or web page 
      InlineQueryResult -> T
description_1 :: T,
      -- | Result thumbnail; may be null
      InlineQueryResult -> PhotoSize
thumbnail_1 :: PhotoSize
    }
  | -- | Represents a user contact 
  InlineQueryResultContact
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_2 :: T,
      -- | A user contact 
      InlineQueryResult -> Contact
contact_2 :: Contact,
      -- | Result thumbnail; may be null
      InlineQueryResult -> PhotoSize
thumbnail_2 :: PhotoSize
    }
  | -- | Represents a point on the map 
  InlineQueryResultLocation
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_3 :: T,
      -- | Location result 
      InlineQueryResult -> Location
location_3 :: Location,
      -- | Title of the result 
      InlineQueryResult -> T
title_3 :: T,
      -- | Result thumbnail; may be null
      InlineQueryResult -> PhotoSize
thumbnail_3 :: PhotoSize
    }
  | -- | Represents information about a venue 
  InlineQueryResultVenue
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_4 :: T,
      -- | Venue result 
      InlineQueryResult -> Venue
venue_4 :: Venue,
      -- | Result thumbnail; may be null
      InlineQueryResult -> PhotoSize
thumbnail_4 :: PhotoSize
    }
  | -- | Represents information about a game 
  InlineQueryResultGame
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_5 :: T,
      -- | Game result
      InlineQueryResult -> Game
game_5 :: Game
    }
  | -- | Represents an animation file 
  InlineQueryResultAnimation
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_6 :: T,
      -- | Animation file 
      InlineQueryResult -> Animation
animation_6 :: Animation,
      -- | Animation title
      InlineQueryResult -> T
title_6 :: T
    }
  | -- | Represents an audio file 
  InlineQueryResultAudio
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_7 :: T,
      -- | Audio file
      InlineQueryResult -> Audio
audio_7 :: Audio
    }
  | -- | Represents a document 
  InlineQueryResultDocument
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_8 :: T,
      -- | Document 
      InlineQueryResult -> Document
document_8 :: Document,
      -- | Document title 
      InlineQueryResult -> T
title_8 :: T,
      -- | Represents a document 
      InlineQueryResult -> T
description_8 :: T
    }
  | -- | Represents a photo 
  InlineQueryResultPhoto
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_9 :: T,
      -- | Photo 
      InlineQueryResult -> Photo
photo_9 :: Photo,
      -- | Title of the result, if known 
      InlineQueryResult -> T
title_9 :: T,
      -- | Represents a photo 
      InlineQueryResult -> T
description_9 :: T
    }
  | -- | Represents a sticker 
  InlineQueryResultSticker
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_10 :: T,
      -- | Sticker
      InlineQueryResult -> Sticker
sticker_10 :: Sticker
    }
  | -- | Represents a video 
  InlineQueryResultVideo
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_11 :: T,
      -- | Video 
      InlineQueryResult -> Video
video_11 :: Video,
      -- | Title of the video 
      InlineQueryResult -> T
title_11 :: T,
      -- | Represents a video 
      InlineQueryResult -> T
description_11 :: T
    }
  | -- | Represents a voice note 
  InlineQueryResultVoiceNote
    { -- | Unique identifier of the query result 
      InlineQueryResult -> T
id_12 :: T,
      -- | Voice note 
      InlineQueryResult -> VoiceNote
voice_note_12 :: VoiceNote,
      -- | Title of the voice note
      InlineQueryResult -> T
title_12 :: T
    }
  deriving (I32 -> InlineQueryResult -> ShowS
[InlineQueryResult] -> ShowS
InlineQueryResult -> String
(I32 -> InlineQueryResult -> ShowS)
-> (InlineQueryResult -> String)
-> ([InlineQueryResult] -> ShowS)
-> Show InlineQueryResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryResult] -> ShowS
$cshowList :: [InlineQueryResult] -> ShowS
show :: InlineQueryResult -> String
$cshow :: InlineQueryResult -> String
showsPrec :: I32 -> InlineQueryResult -> ShowS
$cshowsPrec :: I32 -> InlineQueryResult -> ShowS
Show, InlineQueryResult -> InlineQueryResult -> Bool
(InlineQueryResult -> InlineQueryResult -> Bool)
-> (InlineQueryResult -> InlineQueryResult -> Bool)
-> Eq InlineQueryResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineQueryResult -> InlineQueryResult -> Bool
$c/= :: InlineQueryResult -> InlineQueryResult -> Bool
== :: InlineQueryResult -> InlineQueryResult -> Bool
$c== :: InlineQueryResult -> InlineQueryResult -> Bool
Eq, (forall x. InlineQueryResult -> Rep InlineQueryResult x)
-> (forall x. Rep InlineQueryResult x -> InlineQueryResult)
-> Generic InlineQueryResult
forall x. Rep InlineQueryResult x -> InlineQueryResult
forall x. InlineQueryResult -> Rep InlineQueryResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryResult x -> InlineQueryResult
$cfrom :: forall x. InlineQueryResult -> Rep InlineQueryResult x
Generic)
data InlineQueryResults
  = -- | Represents the results of the inline query. Use sendInlineQueryResultMessage to send the result of the query 
  InlineQueryResults
    { -- | Unique identifier of the inline query 
      InlineQueryResults -> I64
inline_query_id_1 :: I64,
      -- | The offset for the next request. If empty, there are no more results 
      InlineQueryResults -> T
next_offset_1 :: T,
      -- | Results of the query
      InlineQueryResults -> [InlineQueryResult]
results_1 :: ([]) (InlineQueryResult),
      -- | If non-empty, this text should be shown on the button, which opens a private chat with the bot and sends the bot a start message with the switch_pm_parameter 
      InlineQueryResults -> T
switch_pm_text_1 :: T,
      -- | Parameter for the bot start message
      InlineQueryResults -> T
switch_pm_parameter_1 :: T
    }
  deriving (I32 -> InlineQueryResults -> ShowS
[InlineQueryResults] -> ShowS
InlineQueryResults -> String
(I32 -> InlineQueryResults -> ShowS)
-> (InlineQueryResults -> String)
-> ([InlineQueryResults] -> ShowS)
-> Show InlineQueryResults
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InlineQueryResults] -> ShowS
$cshowList :: [InlineQueryResults] -> ShowS
show :: InlineQueryResults -> String
$cshow :: InlineQueryResults -> String
showsPrec :: I32 -> InlineQueryResults -> ShowS
$cshowsPrec :: I32 -> InlineQueryResults -> ShowS
Show, InlineQueryResults -> InlineQueryResults -> Bool
(InlineQueryResults -> InlineQueryResults -> Bool)
-> (InlineQueryResults -> InlineQueryResults -> Bool)
-> Eq InlineQueryResults
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineQueryResults -> InlineQueryResults -> Bool
$c/= :: InlineQueryResults -> InlineQueryResults -> Bool
== :: InlineQueryResults -> InlineQueryResults -> Bool
$c== :: InlineQueryResults -> InlineQueryResults -> Bool
Eq, (forall x. InlineQueryResults -> Rep InlineQueryResults x)
-> (forall x. Rep InlineQueryResults x -> InlineQueryResults)
-> Generic InlineQueryResults
forall x. Rep InlineQueryResults x -> InlineQueryResults
forall x. InlineQueryResults -> Rep InlineQueryResults x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InlineQueryResults x -> InlineQueryResults
$cfrom :: forall x. InlineQueryResults -> Rep InlineQueryResults x
Generic)
-- | Represents a payload of a callback query
data CallbackQueryPayload
  = -- | The payload from a general callback button 
  CallbackQueryPayloadData
    { -- | Data that was attached to the callback button
      CallbackQueryPayload -> ByteString64
data_1 :: ByteString64
    }
  | -- | The payload from a game callback button 
  CallbackQueryPayloadGame
    { -- | A short name of the game that was attached to the callback button
      CallbackQueryPayload -> T
game_short_name_2 :: T
    }
  deriving (I32 -> CallbackQueryPayload -> ShowS
[CallbackQueryPayload] -> ShowS
CallbackQueryPayload -> String
(I32 -> CallbackQueryPayload -> ShowS)
-> (CallbackQueryPayload -> String)
-> ([CallbackQueryPayload] -> ShowS)
-> Show CallbackQueryPayload
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallbackQueryPayload] -> ShowS
$cshowList :: [CallbackQueryPayload] -> ShowS
show :: CallbackQueryPayload -> String
$cshow :: CallbackQueryPayload -> String
showsPrec :: I32 -> CallbackQueryPayload -> ShowS
$cshowsPrec :: I32 -> CallbackQueryPayload -> ShowS
Show, CallbackQueryPayload -> CallbackQueryPayload -> Bool
(CallbackQueryPayload -> CallbackQueryPayload -> Bool)
-> (CallbackQueryPayload -> CallbackQueryPayload -> Bool)
-> Eq CallbackQueryPayload
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallbackQueryPayload -> CallbackQueryPayload -> Bool
$c/= :: CallbackQueryPayload -> CallbackQueryPayload -> Bool
== :: CallbackQueryPayload -> CallbackQueryPayload -> Bool
$c== :: CallbackQueryPayload -> CallbackQueryPayload -> Bool
Eq, (forall x. CallbackQueryPayload -> Rep CallbackQueryPayload x)
-> (forall x. Rep CallbackQueryPayload x -> CallbackQueryPayload)
-> Generic CallbackQueryPayload
forall x. Rep CallbackQueryPayload x -> CallbackQueryPayload
forall x. CallbackQueryPayload -> Rep CallbackQueryPayload x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallbackQueryPayload x -> CallbackQueryPayload
$cfrom :: forall x. CallbackQueryPayload -> Rep CallbackQueryPayload x
Generic)
data CallbackQueryAnswer
  = -- | Contains a bot's answer to a callback query 
  CallbackQueryAnswer
    { -- | Text of the answer 
      CallbackQueryAnswer -> T
text_1 :: T,
      -- | True, if an alert should be shown to the user instead of a toast notification 
      CallbackQueryAnswer -> Bool
show_alert_1 :: Bool,
      -- | URL to be opened
      CallbackQueryAnswer -> T
url_1 :: T
    }
  deriving (I32 -> CallbackQueryAnswer -> ShowS
[CallbackQueryAnswer] -> ShowS
CallbackQueryAnswer -> String
(I32 -> CallbackQueryAnswer -> ShowS)
-> (CallbackQueryAnswer -> String)
-> ([CallbackQueryAnswer] -> ShowS)
-> Show CallbackQueryAnswer
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CallbackQueryAnswer] -> ShowS
$cshowList :: [CallbackQueryAnswer] -> ShowS
show :: CallbackQueryAnswer -> String
$cshow :: CallbackQueryAnswer -> String
showsPrec :: I32 -> CallbackQueryAnswer -> ShowS
$cshowsPrec :: I32 -> CallbackQueryAnswer -> ShowS
Show, CallbackQueryAnswer -> CallbackQueryAnswer -> Bool
(CallbackQueryAnswer -> CallbackQueryAnswer -> Bool)
-> (CallbackQueryAnswer -> CallbackQueryAnswer -> Bool)
-> Eq CallbackQueryAnswer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CallbackQueryAnswer -> CallbackQueryAnswer -> Bool
$c/= :: CallbackQueryAnswer -> CallbackQueryAnswer -> Bool
== :: CallbackQueryAnswer -> CallbackQueryAnswer -> Bool
$c== :: CallbackQueryAnswer -> CallbackQueryAnswer -> Bool
Eq, (forall x. CallbackQueryAnswer -> Rep CallbackQueryAnswer x)
-> (forall x. Rep CallbackQueryAnswer x -> CallbackQueryAnswer)
-> Generic CallbackQueryAnswer
forall x. Rep CallbackQueryAnswer x -> CallbackQueryAnswer
forall x. CallbackQueryAnswer -> Rep CallbackQueryAnswer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CallbackQueryAnswer x -> CallbackQueryAnswer
$cfrom :: forall x. CallbackQueryAnswer -> Rep CallbackQueryAnswer x
Generic)
data CustomRequestResult
  = -- | Contains the result of a custom request 
  CustomRequestResult
    { -- | A JSON-serialized result
      CustomRequestResult -> T
result_1 :: T
    }
  deriving (I32 -> CustomRequestResult -> ShowS
[CustomRequestResult] -> ShowS
CustomRequestResult -> String
(I32 -> CustomRequestResult -> ShowS)
-> (CustomRequestResult -> String)
-> ([CustomRequestResult] -> ShowS)
-> Show CustomRequestResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CustomRequestResult] -> ShowS
$cshowList :: [CustomRequestResult] -> ShowS
show :: CustomRequestResult -> String
$cshow :: CustomRequestResult -> String
showsPrec :: I32 -> CustomRequestResult -> ShowS
$cshowsPrec :: I32 -> CustomRequestResult -> ShowS
Show, CustomRequestResult -> CustomRequestResult -> Bool
(CustomRequestResult -> CustomRequestResult -> Bool)
-> (CustomRequestResult -> CustomRequestResult -> Bool)
-> Eq CustomRequestResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CustomRequestResult -> CustomRequestResult -> Bool
$c/= :: CustomRequestResult -> CustomRequestResult -> Bool
== :: CustomRequestResult -> CustomRequestResult -> Bool
$c== :: CustomRequestResult -> CustomRequestResult -> Bool
Eq, (forall x. CustomRequestResult -> Rep CustomRequestResult x)
-> (forall x. Rep CustomRequestResult x -> CustomRequestResult)
-> Generic CustomRequestResult
forall x. Rep CustomRequestResult x -> CustomRequestResult
forall x. CustomRequestResult -> Rep CustomRequestResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CustomRequestResult x -> CustomRequestResult
$cfrom :: forall x. CustomRequestResult -> Rep CustomRequestResult x
Generic)
data GameHighScore
  = -- | Contains one row of the game high score table 
  GameHighScore
    { -- | Position in the high score table 
      GameHighScore -> I32
position_1 :: I32,
      -- | User identifier 
      GameHighScore -> I32
user_id_1 :: I32,
      -- | User score
      GameHighScore -> I32
score_1 :: I32
    }
  deriving (I32 -> GameHighScore -> ShowS
[GameHighScore] -> ShowS
GameHighScore -> String
(I32 -> GameHighScore -> ShowS)
-> (GameHighScore -> String)
-> ([GameHighScore] -> ShowS)
-> Show GameHighScore
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GameHighScore] -> ShowS
$cshowList :: [GameHighScore] -> ShowS
show :: GameHighScore -> String
$cshow :: GameHighScore -> String
showsPrec :: I32 -> GameHighScore -> ShowS
$cshowsPrec :: I32 -> GameHighScore -> ShowS
Show, GameHighScore -> GameHighScore -> Bool
(GameHighScore -> GameHighScore -> Bool)
-> (GameHighScore -> GameHighScore -> Bool) -> Eq GameHighScore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GameHighScore -> GameHighScore -> Bool
$c/= :: GameHighScore -> GameHighScore -> Bool
== :: GameHighScore -> GameHighScore -> Bool
$c== :: GameHighScore -> GameHighScore -> Bool
Eq, (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)
data GameHighScores
  = -- | Contains a list of game high scores 
  GameHighScores
    { -- | A list of game high scores
      GameHighScores -> [GameHighScore]
scores_1 :: ([]) (GameHighScore)
    }
  deriving (I32 -> GameHighScores -> ShowS
[GameHighScores] -> ShowS
GameHighScores -> String
(I32 -> GameHighScores -> ShowS)
-> (GameHighScores -> String)
-> ([GameHighScores] -> ShowS)
-> Show GameHighScores
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GameHighScores] -> ShowS
$cshowList :: [GameHighScores] -> ShowS
show :: GameHighScores -> String
$cshow :: GameHighScores -> String
showsPrec :: I32 -> GameHighScores -> ShowS
$cshowsPrec :: I32 -> GameHighScores -> ShowS
Show, GameHighScores -> GameHighScores -> Bool
(GameHighScores -> GameHighScores -> Bool)
-> (GameHighScores -> GameHighScores -> Bool) -> Eq GameHighScores
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GameHighScores -> GameHighScores -> Bool
$c/= :: GameHighScores -> GameHighScores -> Bool
== :: GameHighScores -> GameHighScores -> Bool
$c== :: GameHighScores -> GameHighScores -> Bool
Eq, (forall x. GameHighScores -> Rep GameHighScores x)
-> (forall x. Rep GameHighScores x -> GameHighScores)
-> Generic GameHighScores
forall x. Rep GameHighScores x -> GameHighScores
forall x. GameHighScores -> Rep GameHighScores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GameHighScores x -> GameHighScores
$cfrom :: forall x. GameHighScores -> Rep GameHighScores x
Generic)
-- | Represents a chat event
data ChatEventAction
  = -- | A message was edited 
  ChatEventMessageEdited
    { -- | The original message before the edit 
      ChatEventAction -> Message
old_message_1 :: Message,
      -- | The message after it was edited
      ChatEventAction -> Message
new_message_1 :: Message
    }
  | -- | A message was deleted 
  ChatEventMessageDeleted
    { -- | Deleted message
      ChatEventAction -> Message
message_2 :: Message
    }
  | -- | A poll in a message was stopped 
  ChatEventPollStopped
    { -- | The message with the poll
      ChatEventAction -> Message
message_3 :: Message
    }
  | -- | A message was pinned 
  ChatEventMessagePinned
    { -- | Pinned message
      ChatEventAction -> Message
message_4 :: Message
    }
  | -- | A message was unpinned
  ChatEventMessageUnpinned
    { 
    }
  | -- | A new member joined the chat
  ChatEventMemberJoined
    { 
    }
  | -- | A member left the chat
  ChatEventMemberLeft
    { 
    }
  | -- | A new chat member was invited 
  ChatEventMemberInvited
    { -- | New member user identifier 
      ChatEventAction -> I32
user_id_8 :: I32,
      -- | New member status
      ChatEventAction -> ChatMemberStatus
status_8 :: ChatMemberStatus
    }
  | -- | A chat member has gained/lost administrator status, or the list of their administrator privileges has changed 
  ChatEventMemberPromoted
    { -- | Chat member user identifier 
      ChatEventAction -> I32
user_id_9 :: I32,
      -- | Previous status of the chat member 
      ChatEventAction -> ChatMemberStatus
old_status_9 :: ChatMemberStatus,
      -- | New status of the chat member
      ChatEventAction -> ChatMemberStatus
new_status_9 :: ChatMemberStatus
    }
  | -- | A chat member was restricted/unrestricted or banned/unbanned, or the list of their restrictions has changed 
  ChatEventMemberRestricted
    { -- | Chat member user identifier 
      ChatEventAction -> I32
user_id_10 :: I32,
      -- | Previous status of the chat member 
      ChatEventAction -> ChatMemberStatus
old_status_10 :: ChatMemberStatus,
      -- | New status of the chat member
      ChatEventAction -> ChatMemberStatus
new_status_10 :: ChatMemberStatus
    }
  | -- | The chat title was changed 
  ChatEventTitleChanged
    { -- | Previous chat title 
      ChatEventAction -> T
old_title_11 :: T,
      -- | New chat title
      ChatEventAction -> T
new_title_11 :: T
    }
  | -- | The chat permissions was changed 
  ChatEventPermissionsChanged
    { -- | Previous chat permissions 
      ChatEventAction -> ChatPermissions
old_permissions_12 :: ChatPermissions,
      -- | New chat permissions
      ChatEventAction -> ChatPermissions
new_permissions_12 :: ChatPermissions
    }
  | -- | The chat description was changed 
  ChatEventDescriptionChanged
    { -- | Previous chat description 
      ChatEventAction -> T
old_description_13 :: T,
      -- | New chat description
      ChatEventAction -> T
new_description_13 :: T
    }
  | -- | The chat username was changed 
  ChatEventUsernameChanged
    { -- | Previous chat username 
      ChatEventAction -> T
old_username_14 :: T,
      -- | New chat username
      ChatEventAction -> T
new_username_14 :: T
    }
  | -- | The chat photo was changed 
  ChatEventPhotoChanged
    { -- | Previous chat photo value; may be null 
      ChatEventAction -> Photo
old_photo_15 :: Photo,
      -- | New chat photo value; may be null
      ChatEventAction -> Photo
new_photo_15 :: Photo
    }
  | -- | The can_invite_users permission of a supergroup chat was toggled 
  ChatEventInvitesToggled
    { -- | New value of can_invite_users permission
      ChatEventAction -> Bool
can_invite_users_16 :: Bool
    }
  | -- | The linked chat of a supergroup was changed 
  ChatEventLinkedChatChanged
    { -- | Previous supergroup linked chat identifier 
      ChatEventAction -> I32
old_linked_chat_id_17 :: I53,
      -- | New supergroup linked chat identifier
      ChatEventAction -> I32
new_linked_chat_id_17 :: I53
    }
  | -- | The slow_mode_delay setting of a supergroup was changed 
  ChatEventSlowModeDelayChanged
    { -- | Previous value of slow_mode_delay 
      ChatEventAction -> I32
old_slow_mode_delay_18 :: I32,
      -- | New value of slow_mode_delay
      ChatEventAction -> I32
new_slow_mode_delay_18 :: I32
    }
  | -- | The sign_messages setting of a channel was toggled 
  ChatEventSignMessagesToggled
    { -- | New value of sign_messages
      ChatEventAction -> Bool
sign_messages_19 :: Bool
    }
  | -- | The supergroup sticker set was changed 
  ChatEventStickerSetChanged
    { -- | Previous identifier of the chat sticker set; 0 if none 
      ChatEventAction -> I64
old_sticker_set_id_20 :: I64,
      -- | New identifier of the chat sticker set; 0 if none
      ChatEventAction -> I64
new_sticker_set_id_20 :: I64
    }
  | -- | The supergroup location was changed 
  ChatEventLocationChanged
    { -- | Previous location; may be null 
      ChatEventAction -> ChatLocation
old_location_21 :: ChatLocation,
      -- | New location; may be null
      ChatEventAction -> ChatLocation
new_location_21 :: ChatLocation
    }
  | -- | The is_all_history_available setting of a supergroup was toggled 
  ChatEventIsAllHistoryAvailableToggled
    { -- | New value of is_all_history_available
      ChatEventAction -> Bool
is_all_history_available_22 :: Bool
    }
  deriving (I32 -> ChatEventAction -> ShowS
[ChatEventAction] -> ShowS
ChatEventAction -> String
(I32 -> ChatEventAction -> ShowS)
-> (ChatEventAction -> String)
-> ([ChatEventAction] -> ShowS)
-> Show ChatEventAction
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatEventAction] -> ShowS
$cshowList :: [ChatEventAction] -> ShowS
show :: ChatEventAction -> String
$cshow :: ChatEventAction -> String
showsPrec :: I32 -> ChatEventAction -> ShowS
$cshowsPrec :: I32 -> ChatEventAction -> ShowS
Show, ChatEventAction -> ChatEventAction -> Bool
(ChatEventAction -> ChatEventAction -> Bool)
-> (ChatEventAction -> ChatEventAction -> Bool)
-> Eq ChatEventAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatEventAction -> ChatEventAction -> Bool
$c/= :: ChatEventAction -> ChatEventAction -> Bool
== :: ChatEventAction -> ChatEventAction -> Bool
$c== :: ChatEventAction -> ChatEventAction -> Bool
Eq, (forall x. ChatEventAction -> Rep ChatEventAction x)
-> (forall x. Rep ChatEventAction x -> ChatEventAction)
-> Generic ChatEventAction
forall x. Rep ChatEventAction x -> ChatEventAction
forall x. ChatEventAction -> Rep ChatEventAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatEventAction x -> ChatEventAction
$cfrom :: forall x. ChatEventAction -> Rep ChatEventAction x
Generic)
data ChatEvent
  = -- | Represents a chat event 
  ChatEvent
    { -- | Chat event identifier 
      ChatEvent -> I64
id_1 :: I64,
      -- | Point in time (Unix timestamp) when the event happened 
      ChatEvent -> I32
date_1 :: I32,
      -- | Identifier of the user who performed the action that triggered the event 
      ChatEvent -> I32
user_id_1 :: I32,
      -- | Action performed by the user
      ChatEvent -> ChatEventAction
action_1 :: ChatEventAction
    }
  deriving (I32 -> ChatEvent -> ShowS
[ChatEvent] -> ShowS
ChatEvent -> String
(I32 -> ChatEvent -> ShowS)
-> (ChatEvent -> String)
-> ([ChatEvent] -> ShowS)
-> Show ChatEvent
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatEvent] -> ShowS
$cshowList :: [ChatEvent] -> ShowS
show :: ChatEvent -> String
$cshow :: ChatEvent -> String
showsPrec :: I32 -> ChatEvent -> ShowS
$cshowsPrec :: I32 -> ChatEvent -> ShowS
Show, ChatEvent -> ChatEvent -> Bool
(ChatEvent -> ChatEvent -> Bool)
-> (ChatEvent -> ChatEvent -> Bool) -> Eq ChatEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatEvent -> ChatEvent -> Bool
$c/= :: ChatEvent -> ChatEvent -> Bool
== :: ChatEvent -> ChatEvent -> Bool
$c== :: ChatEvent -> ChatEvent -> Bool
Eq, (forall x. ChatEvent -> Rep ChatEvent x)
-> (forall x. Rep ChatEvent x -> ChatEvent) -> Generic ChatEvent
forall x. Rep ChatEvent x -> ChatEvent
forall x. ChatEvent -> Rep ChatEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatEvent x -> ChatEvent
$cfrom :: forall x. ChatEvent -> Rep ChatEvent x
Generic)
data ChatEvents
  = -- | Contains a list of chat events 
  ChatEvents
    { -- | List of events
      ChatEvents -> [ChatEvent]
events_1 :: ([]) (ChatEvent)
    }
  deriving (I32 -> ChatEvents -> ShowS
[ChatEvents] -> ShowS
ChatEvents -> String
(I32 -> ChatEvents -> ShowS)
-> (ChatEvents -> String)
-> ([ChatEvents] -> ShowS)
-> Show ChatEvents
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatEvents] -> ShowS
$cshowList :: [ChatEvents] -> ShowS
show :: ChatEvents -> String
$cshow :: ChatEvents -> String
showsPrec :: I32 -> ChatEvents -> ShowS
$cshowsPrec :: I32 -> ChatEvents -> ShowS
Show, ChatEvents -> ChatEvents -> Bool
(ChatEvents -> ChatEvents -> Bool)
-> (ChatEvents -> ChatEvents -> Bool) -> Eq ChatEvents
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatEvents -> ChatEvents -> Bool
$c/= :: ChatEvents -> ChatEvents -> Bool
== :: ChatEvents -> ChatEvents -> Bool
$c== :: ChatEvents -> ChatEvents -> Bool
Eq, (forall x. ChatEvents -> Rep ChatEvents x)
-> (forall x. Rep ChatEvents x -> ChatEvents) -> Generic ChatEvents
forall x. Rep ChatEvents x -> ChatEvents
forall x. ChatEvents -> Rep ChatEvents x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatEvents x -> ChatEvents
$cfrom :: forall x. ChatEvents -> Rep ChatEvents x
Generic)
data ChatEventLogFilters
  = -- | Represents a set of filters used to obtain a chat event log
  ChatEventLogFilters
    { -- | True, if message edits should be returned
      ChatEventLogFilters -> Bool
message_edits_1 :: Bool,
      -- | True, if message deletions should be returned
      ChatEventLogFilters -> Bool
message_deletions_1 :: Bool,
      -- | True, if pin/unpin events should be returned
      ChatEventLogFilters -> Bool
message_pins_1 :: Bool,
      -- | True, if members joining events should be returned
      ChatEventLogFilters -> Bool
member_joins_1 :: Bool,
      -- | True, if members leaving events should be returned
      ChatEventLogFilters -> Bool
member_leaves_1 :: Bool,
      -- | True, if invited member events should be returned
      ChatEventLogFilters -> Bool
member_invites_1 :: Bool,
      -- | True, if member promotion/demotion events should be returned
      ChatEventLogFilters -> Bool
member_promotions_1 :: Bool,
      -- | True, if member restricted/unrestricted/banned/unbanned events should be returned
      ChatEventLogFilters -> Bool
member_restrictions_1 :: Bool,
      -- | True, if changes in chat information should be returned
      ChatEventLogFilters -> Bool
info_changes_1 :: Bool,
      -- | True, if changes in chat settings should be returned
      ChatEventLogFilters -> Bool
setting_changes_1 :: Bool
    }
  deriving (I32 -> ChatEventLogFilters -> ShowS
[ChatEventLogFilters] -> ShowS
ChatEventLogFilters -> String
(I32 -> ChatEventLogFilters -> ShowS)
-> (ChatEventLogFilters -> String)
-> ([ChatEventLogFilters] -> ShowS)
-> Show ChatEventLogFilters
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatEventLogFilters] -> ShowS
$cshowList :: [ChatEventLogFilters] -> ShowS
show :: ChatEventLogFilters -> String
$cshow :: ChatEventLogFilters -> String
showsPrec :: I32 -> ChatEventLogFilters -> ShowS
$cshowsPrec :: I32 -> ChatEventLogFilters -> ShowS
Show, ChatEventLogFilters -> ChatEventLogFilters -> Bool
(ChatEventLogFilters -> ChatEventLogFilters -> Bool)
-> (ChatEventLogFilters -> ChatEventLogFilters -> Bool)
-> Eq ChatEventLogFilters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatEventLogFilters -> ChatEventLogFilters -> Bool
$c/= :: ChatEventLogFilters -> ChatEventLogFilters -> Bool
== :: ChatEventLogFilters -> ChatEventLogFilters -> Bool
$c== :: ChatEventLogFilters -> ChatEventLogFilters -> Bool
Eq, (forall x. ChatEventLogFilters -> Rep ChatEventLogFilters x)
-> (forall x. Rep ChatEventLogFilters x -> ChatEventLogFilters)
-> Generic ChatEventLogFilters
forall x. Rep ChatEventLogFilters x -> ChatEventLogFilters
forall x. ChatEventLogFilters -> Rep ChatEventLogFilters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatEventLogFilters x -> ChatEventLogFilters
$cfrom :: forall x. ChatEventLogFilters -> Rep ChatEventLogFilters x
Generic)
-- | Represents the value of a string in a language pack
data LanguagePackStringValue
  = -- | An ordinary language pack string 
  LanguagePackStringValueOrdinary
    { -- | String value
      LanguagePackStringValue -> T
value_1 :: T
    }
  | -- | A language pack string which has different forms based on the number of some object it mentions. See https://www.unicode.org/cldr/charts/latest/supplemental/language_plural_rules.html for more info
  LanguagePackStringValuePluralized
    { -- | Value for zero objects 
      LanguagePackStringValue -> T
zero_value_2 :: T,
      -- | Value for one object 
      LanguagePackStringValue -> T
one_value_2 :: T,
      -- | Value for two objects
      LanguagePackStringValue -> T
two_value_2 :: T,
      -- | Value for few objects 
      LanguagePackStringValue -> T
few_value_2 :: T,
      -- | Value for many objects 
      LanguagePackStringValue -> T
many_value_2 :: T,
      -- | Default value
      LanguagePackStringValue -> T
other_value_2 :: T
    }
  | -- | A deleted language pack string, the value should be taken from the built-in english language pack
  LanguagePackStringValueDeleted
    { 
    }
  deriving (I32 -> LanguagePackStringValue -> ShowS
[LanguagePackStringValue] -> ShowS
LanguagePackStringValue -> String
(I32 -> LanguagePackStringValue -> ShowS)
-> (LanguagePackStringValue -> String)
-> ([LanguagePackStringValue] -> ShowS)
-> Show LanguagePackStringValue
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LanguagePackStringValue] -> ShowS
$cshowList :: [LanguagePackStringValue] -> ShowS
show :: LanguagePackStringValue -> String
$cshow :: LanguagePackStringValue -> String
showsPrec :: I32 -> LanguagePackStringValue -> ShowS
$cshowsPrec :: I32 -> LanguagePackStringValue -> ShowS
Show, LanguagePackStringValue -> LanguagePackStringValue -> Bool
(LanguagePackStringValue -> LanguagePackStringValue -> Bool)
-> (LanguagePackStringValue -> LanguagePackStringValue -> Bool)
-> Eq LanguagePackStringValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LanguagePackStringValue -> LanguagePackStringValue -> Bool
$c/= :: LanguagePackStringValue -> LanguagePackStringValue -> Bool
== :: LanguagePackStringValue -> LanguagePackStringValue -> Bool
$c== :: LanguagePackStringValue -> LanguagePackStringValue -> Bool
Eq, (forall x.
 LanguagePackStringValue -> Rep LanguagePackStringValue x)
-> (forall x.
    Rep LanguagePackStringValue x -> LanguagePackStringValue)
-> Generic LanguagePackStringValue
forall x. Rep LanguagePackStringValue x -> LanguagePackStringValue
forall x. LanguagePackStringValue -> Rep LanguagePackStringValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LanguagePackStringValue x -> LanguagePackStringValue
$cfrom :: forall x. LanguagePackStringValue -> Rep LanguagePackStringValue x
Generic)
data LanguagePackString
  = -- | Represents one language pack string 
  LanguagePackString
    { -- | String key 
      LanguagePackString -> T
key_1 :: T,
      -- | String value
      LanguagePackString -> LanguagePackStringValue
value_1 :: LanguagePackStringValue
    }
  deriving (I32 -> LanguagePackString -> ShowS
[LanguagePackString] -> ShowS
LanguagePackString -> String
(I32 -> LanguagePackString -> ShowS)
-> (LanguagePackString -> String)
-> ([LanguagePackString] -> ShowS)
-> Show LanguagePackString
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LanguagePackString] -> ShowS
$cshowList :: [LanguagePackString] -> ShowS
show :: LanguagePackString -> String
$cshow :: LanguagePackString -> String
showsPrec :: I32 -> LanguagePackString -> ShowS
$cshowsPrec :: I32 -> LanguagePackString -> ShowS
Show, LanguagePackString -> LanguagePackString -> Bool
(LanguagePackString -> LanguagePackString -> Bool)
-> (LanguagePackString -> LanguagePackString -> Bool)
-> Eq LanguagePackString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LanguagePackString -> LanguagePackString -> Bool
$c/= :: LanguagePackString -> LanguagePackString -> Bool
== :: LanguagePackString -> LanguagePackString -> Bool
$c== :: LanguagePackString -> LanguagePackString -> Bool
Eq, (forall x. LanguagePackString -> Rep LanguagePackString x)
-> (forall x. Rep LanguagePackString x -> LanguagePackString)
-> Generic LanguagePackString
forall x. Rep LanguagePackString x -> LanguagePackString
forall x. LanguagePackString -> Rep LanguagePackString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LanguagePackString x -> LanguagePackString
$cfrom :: forall x. LanguagePackString -> Rep LanguagePackString x
Generic)
data LanguagePackStrings
  = -- | Contains a list of language pack strings 
  LanguagePackStrings
    { -- | A list of language pack strings
      LanguagePackStrings -> [LanguagePackString]
strings_1 :: ([]) (LanguagePackString)
    }
  deriving (I32 -> LanguagePackStrings -> ShowS
[LanguagePackStrings] -> ShowS
LanguagePackStrings -> String
(I32 -> LanguagePackStrings -> ShowS)
-> (LanguagePackStrings -> String)
-> ([LanguagePackStrings] -> ShowS)
-> Show LanguagePackStrings
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LanguagePackStrings] -> ShowS
$cshowList :: [LanguagePackStrings] -> ShowS
show :: LanguagePackStrings -> String
$cshow :: LanguagePackStrings -> String
showsPrec :: I32 -> LanguagePackStrings -> ShowS
$cshowsPrec :: I32 -> LanguagePackStrings -> ShowS
Show, LanguagePackStrings -> LanguagePackStrings -> Bool
(LanguagePackStrings -> LanguagePackStrings -> Bool)
-> (LanguagePackStrings -> LanguagePackStrings -> Bool)
-> Eq LanguagePackStrings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LanguagePackStrings -> LanguagePackStrings -> Bool
$c/= :: LanguagePackStrings -> LanguagePackStrings -> Bool
== :: LanguagePackStrings -> LanguagePackStrings -> Bool
$c== :: LanguagePackStrings -> LanguagePackStrings -> Bool
Eq, (forall x. LanguagePackStrings -> Rep LanguagePackStrings x)
-> (forall x. Rep LanguagePackStrings x -> LanguagePackStrings)
-> Generic LanguagePackStrings
forall x. Rep LanguagePackStrings x -> LanguagePackStrings
forall x. LanguagePackStrings -> Rep LanguagePackStrings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LanguagePackStrings x -> LanguagePackStrings
$cfrom :: forall x. LanguagePackStrings -> Rep LanguagePackStrings x
Generic)
data LanguagePackInfo
  = -- | Contains information about a language pack 
  LanguagePackInfo
    { -- | Unique language pack identifier
      LanguagePackInfo -> T
id_1 :: T,
      -- | Identifier of a base language pack; may be empty. If a string is missed in the language pack, then it should be fetched from base language pack. Unsupported in custom language packs
      LanguagePackInfo -> T
base_language_pack_id_1 :: T,
      -- | Language name 
      LanguagePackInfo -> T
name_1 :: T,
      -- | Name of the language in that language
      LanguagePackInfo -> T
native_name_1 :: T,
      -- | A language code to be used to apply plural forms. See https://www.unicode.org/cldr/charts/latest/supplemental/language_plural_rules.html for more info
      LanguagePackInfo -> T
plural_code_1 :: T,
      -- | True, if the language pack is official 
      LanguagePackInfo -> Bool
is_official_1 :: Bool,
      -- | True, if the language pack strings are RTL 
      LanguagePackInfo -> Bool
is_rtl_1 :: Bool,
      -- | True, if the language pack is a beta language pack
      LanguagePackInfo -> Bool
is_beta_1 :: Bool,
      -- | True, if the language pack is installed by the current user
      LanguagePackInfo -> Bool
is_installed_1 :: Bool,
      -- | Total number of non-deleted strings from the language pack 
      LanguagePackInfo -> I32
total_string_count_1 :: I32,
      -- | Total number of translated strings from the language pack
      LanguagePackInfo -> I32
translated_string_count_1 :: I32,
      -- | Total number of non-deleted strings from the language pack available locally 
      LanguagePackInfo -> I32
local_string_count_1 :: I32,
      -- | Link to language translation interface; empty for custom local language packs
      LanguagePackInfo -> T
translation_url_1 :: T
    }
  deriving (I32 -> LanguagePackInfo -> ShowS
[LanguagePackInfo] -> ShowS
LanguagePackInfo -> String
(I32 -> LanguagePackInfo -> ShowS)
-> (LanguagePackInfo -> String)
-> ([LanguagePackInfo] -> ShowS)
-> Show LanguagePackInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LanguagePackInfo] -> ShowS
$cshowList :: [LanguagePackInfo] -> ShowS
show :: LanguagePackInfo -> String
$cshow :: LanguagePackInfo -> String
showsPrec :: I32 -> LanguagePackInfo -> ShowS
$cshowsPrec :: I32 -> LanguagePackInfo -> ShowS
Show, LanguagePackInfo -> LanguagePackInfo -> Bool
(LanguagePackInfo -> LanguagePackInfo -> Bool)
-> (LanguagePackInfo -> LanguagePackInfo -> Bool)
-> Eq LanguagePackInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LanguagePackInfo -> LanguagePackInfo -> Bool
$c/= :: LanguagePackInfo -> LanguagePackInfo -> Bool
== :: LanguagePackInfo -> LanguagePackInfo -> Bool
$c== :: LanguagePackInfo -> LanguagePackInfo -> Bool
Eq, (forall x. LanguagePackInfo -> Rep LanguagePackInfo x)
-> (forall x. Rep LanguagePackInfo x -> LanguagePackInfo)
-> Generic LanguagePackInfo
forall x. Rep LanguagePackInfo x -> LanguagePackInfo
forall x. LanguagePackInfo -> Rep LanguagePackInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LanguagePackInfo x -> LanguagePackInfo
$cfrom :: forall x. LanguagePackInfo -> Rep LanguagePackInfo x
Generic)
data LocalizationTargetInfo
  = -- | Contains information about the current localization target 
  LocalizationTargetInfo
    { -- | List of available language packs for this application
      LocalizationTargetInfo -> [LanguagePackInfo]
language_packs_1 :: ([]) (LanguagePackInfo)
    }
  deriving (I32 -> LocalizationTargetInfo -> ShowS
[LocalizationTargetInfo] -> ShowS
LocalizationTargetInfo -> String
(I32 -> LocalizationTargetInfo -> ShowS)
-> (LocalizationTargetInfo -> String)
-> ([LocalizationTargetInfo] -> ShowS)
-> Show LocalizationTargetInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LocalizationTargetInfo] -> ShowS
$cshowList :: [LocalizationTargetInfo] -> ShowS
show :: LocalizationTargetInfo -> String
$cshow :: LocalizationTargetInfo -> String
showsPrec :: I32 -> LocalizationTargetInfo -> ShowS
$cshowsPrec :: I32 -> LocalizationTargetInfo -> ShowS
Show, LocalizationTargetInfo -> LocalizationTargetInfo -> Bool
(LocalizationTargetInfo -> LocalizationTargetInfo -> Bool)
-> (LocalizationTargetInfo -> LocalizationTargetInfo -> Bool)
-> Eq LocalizationTargetInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalizationTargetInfo -> LocalizationTargetInfo -> Bool
$c/= :: LocalizationTargetInfo -> LocalizationTargetInfo -> Bool
== :: LocalizationTargetInfo -> LocalizationTargetInfo -> Bool
$c== :: LocalizationTargetInfo -> LocalizationTargetInfo -> Bool
Eq, (forall x. LocalizationTargetInfo -> Rep LocalizationTargetInfo x)
-> (forall x.
    Rep LocalizationTargetInfo x -> LocalizationTargetInfo)
-> Generic LocalizationTargetInfo
forall x. Rep LocalizationTargetInfo x -> LocalizationTargetInfo
forall x. LocalizationTargetInfo -> Rep LocalizationTargetInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LocalizationTargetInfo x -> LocalizationTargetInfo
$cfrom :: forall x. LocalizationTargetInfo -> Rep LocalizationTargetInfo x
Generic)
-- | Represents a data needed to subscribe for push notifications through registerDevice method. To use specific push notification service, you must specify the correct application platform and upload valid server authentication data at https://my.telegram.org
data DeviceToken
  = -- | A token for Firebase Cloud Messaging 
  DeviceTokenFirebaseCloudMessaging
    { -- | Device registration token; may be empty to de-register a device 
      DeviceToken -> T
token_1 :: T,
      -- | True, if push notifications should be additionally encrypted
      DeviceToken -> Bool
encrypt_1 :: Bool
    }
  | -- | A token for Apple Push Notification service 
  DeviceTokenApplePush
    { -- | Device token; may be empty to de-register a device 
      DeviceToken -> T
device_token_2 :: T,
      -- | True, if App Sandbox is enabled
      DeviceToken -> Bool
is_app_sandbox_2 :: Bool
    }
  | -- | A token for Apple Push Notification service VoIP notifications 
  DeviceTokenApplePushVoIP
    { -- | Device token; may be empty to de-register a device 
      DeviceToken -> T
device_token_3 :: T,
      -- | True, if App Sandbox is enabled 
      DeviceToken -> Bool
is_app_sandbox_3 :: Bool,
      -- | True, if push notifications should be additionally encrypted
      DeviceToken -> Bool
encrypt_3 :: Bool
    }
  | -- | A token for Windows Push Notification Services 
  DeviceTokenWindowsPush
    { -- | The access token that will be used to send notifications; may be empty to de-register a device
      DeviceToken -> T
access_token_4 :: T
    }
  | -- | A token for Microsoft Push Notification Service 
  DeviceTokenMicrosoftPush
    { -- | Push notification channel URI; may be empty to de-register a device
      DeviceToken -> T
channel_uri_5 :: T
    }
  | -- | A token for Microsoft Push Notification Service VoIP channel 
  DeviceTokenMicrosoftPushVoIP
    { -- | Push notification channel URI; may be empty to de-register a device
      DeviceToken -> T
channel_uri_6 :: T
    }
  | -- | A token for web Push API 
  DeviceTokenWebPush
    { -- | Absolute URL exposed by the push service where the application server can send push messages; may be empty to de-register a device
      DeviceToken -> T
endpoint_7 :: T,
      -- | Base64url-encoded P-256 elliptic curve Diffie-Hellman public key 
      DeviceToken -> T
p256dh_base64url_7 :: T,
      -- | Base64url-encoded authentication secret
      DeviceToken -> T
auth_base64url_7 :: T
    }
  | -- | A token for Simple Push API for Firefox OS 
  DeviceTokenSimplePush
    { -- | Absolute URL exposed by the push service where the application server can send push messages; may be empty to de-register a device
      DeviceToken -> T
endpoint_8 :: T
    }
  | -- | A token for Ubuntu Push Client service 
  DeviceTokenUbuntuPush
    { -- | Token; may be empty to de-register a device
      DeviceToken -> T
token_9 :: T
    }
  | -- | A token for BlackBerry Push Service 
  DeviceTokenBlackBerryPush
    { -- | Token; may be empty to de-register a device
      DeviceToken -> T
token_10 :: T
    }
  | -- | A token for Tizen Push Service 
  DeviceTokenTizenPush
    { -- | Push service registration identifier; may be empty to de-register a device
      DeviceToken -> T
reg_id_11 :: T
    }
  deriving (I32 -> DeviceToken -> ShowS
[DeviceToken] -> ShowS
DeviceToken -> String
(I32 -> DeviceToken -> ShowS)
-> (DeviceToken -> String)
-> ([DeviceToken] -> ShowS)
-> Show DeviceToken
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeviceToken] -> ShowS
$cshowList :: [DeviceToken] -> ShowS
show :: DeviceToken -> String
$cshow :: DeviceToken -> String
showsPrec :: I32 -> DeviceToken -> ShowS
$cshowsPrec :: I32 -> DeviceToken -> ShowS
Show, DeviceToken -> DeviceToken -> Bool
(DeviceToken -> DeviceToken -> Bool)
-> (DeviceToken -> DeviceToken -> Bool) -> Eq DeviceToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeviceToken -> DeviceToken -> Bool
$c/= :: DeviceToken -> DeviceToken -> Bool
== :: DeviceToken -> DeviceToken -> Bool
$c== :: DeviceToken -> DeviceToken -> Bool
Eq, (forall x. DeviceToken -> Rep DeviceToken x)
-> (forall x. Rep DeviceToken x -> DeviceToken)
-> Generic DeviceToken
forall x. Rep DeviceToken x -> DeviceToken
forall x. DeviceToken -> Rep DeviceToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeviceToken x -> DeviceToken
$cfrom :: forall x. DeviceToken -> Rep DeviceToken x
Generic)
data PushReceiverId
  = -- | Contains a globally unique push receiver identifier, which can be used to identify which account has received a push notification 
  PushReceiverId
    { -- | The globally unique identifier of push notification subscription
      PushReceiverId -> I64
id_1 :: I64
    }
  deriving (I32 -> PushReceiverId -> ShowS
[PushReceiverId] -> ShowS
PushReceiverId -> String
(I32 -> PushReceiverId -> ShowS)
-> (PushReceiverId -> String)
-> ([PushReceiverId] -> ShowS)
-> Show PushReceiverId
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PushReceiverId] -> ShowS
$cshowList :: [PushReceiverId] -> ShowS
show :: PushReceiverId -> String
$cshow :: PushReceiverId -> String
showsPrec :: I32 -> PushReceiverId -> ShowS
$cshowsPrec :: I32 -> PushReceiverId -> ShowS
Show, PushReceiverId -> PushReceiverId -> Bool
(PushReceiverId -> PushReceiverId -> Bool)
-> (PushReceiverId -> PushReceiverId -> Bool) -> Eq PushReceiverId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PushReceiverId -> PushReceiverId -> Bool
$c/= :: PushReceiverId -> PushReceiverId -> Bool
== :: PushReceiverId -> PushReceiverId -> Bool
$c== :: PushReceiverId -> PushReceiverId -> Bool
Eq, (forall x. PushReceiverId -> Rep PushReceiverId x)
-> (forall x. Rep PushReceiverId x -> PushReceiverId)
-> Generic PushReceiverId
forall x. Rep PushReceiverId x -> PushReceiverId
forall x. PushReceiverId -> Rep PushReceiverId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PushReceiverId x -> PushReceiverId
$cfrom :: forall x. PushReceiverId -> Rep PushReceiverId x
Generic)
-- | Describes a fill of a background
data BackgroundFill
  = -- | Describes a solid fill of a background 
  BackgroundFillSolid
    { -- | A color of the background in the RGB24 format
      BackgroundFill -> I32
color_1 :: I32
    }
  | -- | Describes a gradient fill of a background 
  BackgroundFillGradient
    { -- | A top color of the background in the RGB24 format 
      BackgroundFill -> I32
top_color_2 :: I32,
      -- | A bottom color of the background in the RGB24 format
      BackgroundFill -> I32
bottom_color_2 :: I32,
      -- | Clockwise rotation angle of the gradient, in degrees; 0-359. Should be always divisible by 45
      BackgroundFill -> I32
rotation_angle_2 :: I32
    }
  deriving (I32 -> BackgroundFill -> ShowS
[BackgroundFill] -> ShowS
BackgroundFill -> String
(I32 -> BackgroundFill -> ShowS)
-> (BackgroundFill -> String)
-> ([BackgroundFill] -> ShowS)
-> Show BackgroundFill
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackgroundFill] -> ShowS
$cshowList :: [BackgroundFill] -> ShowS
show :: BackgroundFill -> String
$cshow :: BackgroundFill -> String
showsPrec :: I32 -> BackgroundFill -> ShowS
$cshowsPrec :: I32 -> BackgroundFill -> ShowS
Show, BackgroundFill -> BackgroundFill -> Bool
(BackgroundFill -> BackgroundFill -> Bool)
-> (BackgroundFill -> BackgroundFill -> Bool) -> Eq BackgroundFill
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BackgroundFill -> BackgroundFill -> Bool
$c/= :: BackgroundFill -> BackgroundFill -> Bool
== :: BackgroundFill -> BackgroundFill -> Bool
$c== :: BackgroundFill -> BackgroundFill -> Bool
Eq, (forall x. BackgroundFill -> Rep BackgroundFill x)
-> (forall x. Rep BackgroundFill x -> BackgroundFill)
-> Generic BackgroundFill
forall x. Rep BackgroundFill x -> BackgroundFill
forall x. BackgroundFill -> Rep BackgroundFill x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BackgroundFill x -> BackgroundFill
$cfrom :: forall x. BackgroundFill -> Rep BackgroundFill x
Generic)
-- | Describes the type of a background
data BackgroundType
  = -- | A wallpaper in JPEG format
  BackgroundTypeWallpaper
    { -- | True, if the wallpaper must be downscaled to fit in 450x450 square and then box-blurred with radius 12
      BackgroundType -> Bool
is_blurred_1 :: Bool,
      -- | True, if the background needs to be slightly moved when device is tilted
      BackgroundType -> Bool
is_moving_1 :: Bool
    }
  | -- | A PNG or TGV (gzipped subset of SVG with MIME type "application/x-tgwallpattern") pattern to be combined with the background fill chosen by the user
  BackgroundTypePattern
    { -- | Description of the background fill
      BackgroundType -> BackgroundFill
fill_2 :: BackgroundFill,
      -- | Intensity of the pattern when it is shown above the filled background, 0-100
      BackgroundType -> I32
intensity_2 :: I32,
      -- | True, if the background needs to be slightly moved when device is tilted
      BackgroundType -> Bool
is_moving_2 :: Bool
    }
  | -- | A filled background 
  BackgroundTypeFill
    { -- | Description of the background fill
      BackgroundType -> BackgroundFill
fill_3 :: BackgroundFill
    }
  deriving (I32 -> BackgroundType -> ShowS
[BackgroundType] -> ShowS
BackgroundType -> String
(I32 -> BackgroundType -> ShowS)
-> (BackgroundType -> String)
-> ([BackgroundType] -> ShowS)
-> Show BackgroundType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BackgroundType] -> ShowS
$cshowList :: [BackgroundType] -> ShowS
show :: BackgroundType -> String
$cshow :: BackgroundType -> String
showsPrec :: I32 -> BackgroundType -> ShowS
$cshowsPrec :: I32 -> BackgroundType -> ShowS
Show, BackgroundType -> BackgroundType -> Bool
(BackgroundType -> BackgroundType -> Bool)
-> (BackgroundType -> BackgroundType -> Bool) -> Eq BackgroundType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BackgroundType -> BackgroundType -> Bool
$c/= :: BackgroundType -> BackgroundType -> Bool
== :: BackgroundType -> BackgroundType -> Bool
$c== :: BackgroundType -> BackgroundType -> Bool
Eq, (forall x. BackgroundType -> Rep BackgroundType x)
-> (forall x. Rep BackgroundType x -> BackgroundType)
-> Generic BackgroundType
forall x. Rep BackgroundType x -> BackgroundType
forall x. BackgroundType -> Rep BackgroundType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BackgroundType x -> BackgroundType
$cfrom :: forall x. BackgroundType -> Rep BackgroundType x
Generic)
data Background
  = -- | Describes a chat background
  Background
    { -- | Unique background identifier
      Background -> I64
id_1 :: I64,
      -- | True, if this is one of default backgrounds
      Background -> Bool
is_default_1 :: Bool,
      -- | True, if the background is dark and is recommended to be used with dark theme
      Background -> Bool
is_dark_1 :: Bool,
      -- | Unique background name
      Background -> T
name_1 :: T,
      -- | Document with the background; may be null. Null only for filled backgrounds
      Background -> Document
document_1 :: Document,
      -- | Type of the background
      Background -> BackgroundType
type_1 :: BackgroundType
    }
  deriving (I32 -> Background -> ShowS
[Background] -> ShowS
Background -> String
(I32 -> Background -> ShowS)
-> (Background -> String)
-> ([Background] -> ShowS)
-> Show Background
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Background] -> ShowS
$cshowList :: [Background] -> ShowS
show :: Background -> String
$cshow :: Background -> String
showsPrec :: I32 -> Background -> ShowS
$cshowsPrec :: I32 -> Background -> ShowS
Show, Background -> Background -> Bool
(Background -> Background -> Bool)
-> (Background -> Background -> Bool) -> Eq Background
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Background -> Background -> Bool
$c/= :: Background -> Background -> Bool
== :: Background -> Background -> Bool
$c== :: Background -> Background -> Bool
Eq, (forall x. Background -> Rep Background x)
-> (forall x. Rep Background x -> Background) -> Generic Background
forall x. Rep Background x -> Background
forall x. Background -> Rep Background x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Background x -> Background
$cfrom :: forall x. Background -> Rep Background x
Generic)
data Backgrounds
  = -- | Contains a list of backgrounds 
  Backgrounds
    { -- | A list of backgrounds
      Backgrounds -> [Background]
backgrounds_1 :: ([]) (Background)
    }
  deriving (I32 -> Backgrounds -> ShowS
[Backgrounds] -> ShowS
Backgrounds -> String
(I32 -> Backgrounds -> ShowS)
-> (Backgrounds -> String)
-> ([Backgrounds] -> ShowS)
-> Show Backgrounds
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Backgrounds] -> ShowS
$cshowList :: [Backgrounds] -> ShowS
show :: Backgrounds -> String
$cshow :: Backgrounds -> String
showsPrec :: I32 -> Backgrounds -> ShowS
$cshowsPrec :: I32 -> Backgrounds -> ShowS
Show, Backgrounds -> Backgrounds -> Bool
(Backgrounds -> Backgrounds -> Bool)
-> (Backgrounds -> Backgrounds -> Bool) -> Eq Backgrounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Backgrounds -> Backgrounds -> Bool
$c/= :: Backgrounds -> Backgrounds -> Bool
== :: Backgrounds -> Backgrounds -> Bool
$c== :: Backgrounds -> Backgrounds -> Bool
Eq, (forall x. Backgrounds -> Rep Backgrounds x)
-> (forall x. Rep Backgrounds x -> Backgrounds)
-> Generic Backgrounds
forall x. Rep Backgrounds x -> Backgrounds
forall x. Backgrounds -> Rep Backgrounds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Backgrounds x -> Backgrounds
$cfrom :: forall x. Backgrounds -> Rep Backgrounds x
Generic)
-- | Contains information about background to set
data InputBackground
  = -- | A background from a local file
  InputBackgroundLocal
    { -- | Background file to use. Only inputFileLocal and inputFileGenerated are supported. The file must be in JPEG format for wallpapers and in PNG format for patterns
      InputBackground -> InputFile
background_1 :: InputFile
    }
  | -- | A background from the server 
  InputBackgroundRemote
    { -- | The background identifier
      InputBackground -> I64
background_id_2 :: I64
    }
  deriving (I32 -> InputBackground -> ShowS
[InputBackground] -> ShowS
InputBackground -> String
(I32 -> InputBackground -> ShowS)
-> (InputBackground -> String)
-> ([InputBackground] -> ShowS)
-> Show InputBackground
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputBackground] -> ShowS
$cshowList :: [InputBackground] -> ShowS
show :: InputBackground -> String
$cshow :: InputBackground -> String
showsPrec :: I32 -> InputBackground -> ShowS
$cshowsPrec :: I32 -> InputBackground -> ShowS
Show, InputBackground -> InputBackground -> Bool
(InputBackground -> InputBackground -> Bool)
-> (InputBackground -> InputBackground -> Bool)
-> Eq InputBackground
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputBackground -> InputBackground -> Bool
$c/= :: InputBackground -> InputBackground -> Bool
== :: InputBackground -> InputBackground -> Bool
$c== :: InputBackground -> InputBackground -> Bool
Eq, (forall x. InputBackground -> Rep InputBackground x)
-> (forall x. Rep InputBackground x -> InputBackground)
-> Generic InputBackground
forall x. Rep InputBackground x -> InputBackground
forall x. InputBackground -> Rep InputBackground x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputBackground x -> InputBackground
$cfrom :: forall x. InputBackground -> Rep InputBackground x
Generic)
data Hashtags
  = -- | Contains a list of hashtags 
  Hashtags
    { -- | A list of hashtags
      Hashtags -> [T]
hashtags_1 :: ([]) (T)
    }
  deriving (I32 -> Hashtags -> ShowS
[Hashtags] -> ShowS
Hashtags -> String
(I32 -> Hashtags -> ShowS)
-> (Hashtags -> String) -> ([Hashtags] -> ShowS) -> Show Hashtags
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Hashtags] -> ShowS
$cshowList :: [Hashtags] -> ShowS
show :: Hashtags -> String
$cshow :: Hashtags -> String
showsPrec :: I32 -> Hashtags -> ShowS
$cshowsPrec :: I32 -> Hashtags -> ShowS
Show, Hashtags -> Hashtags -> Bool
(Hashtags -> Hashtags -> Bool)
-> (Hashtags -> Hashtags -> Bool) -> Eq Hashtags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Hashtags -> Hashtags -> Bool
$c/= :: Hashtags -> Hashtags -> Bool
== :: Hashtags -> Hashtags -> Bool
$c== :: Hashtags -> Hashtags -> Bool
Eq, (forall x. Hashtags -> Rep Hashtags x)
-> (forall x. Rep Hashtags x -> Hashtags) -> Generic Hashtags
forall x. Rep Hashtags x -> Hashtags
forall x. Hashtags -> Rep Hashtags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Hashtags x -> Hashtags
$cfrom :: forall x. Hashtags -> Rep Hashtags x
Generic)
-- | Represents result of checking whether the current session can be used to transfer a chat ownership to another user
data CanTransferOwnershipResult
  = -- | The session can be used
  CanTransferOwnershipResultOk
    { 
    }
  | -- | The 2-step verification needs to be enabled first
  CanTransferOwnershipResultPasswordNeeded
    { 
    }
  | -- | The 2-step verification was enabled recently, user needs to wait 
  CanTransferOwnershipResultPasswordTooFresh
    { -- | Time left before the session can be used to transfer ownership of a chat, in seconds
      CanTransferOwnershipResult -> I32
retry_after_3 :: I32
    }
  | -- | The session was created recently, user needs to wait 
  CanTransferOwnershipResultSessionTooFresh
    { -- | Time left before the session can be used to transfer ownership of a chat, in seconds
      CanTransferOwnershipResult -> I32
retry_after_4 :: I32
    }
  deriving (I32 -> CanTransferOwnershipResult -> ShowS
[CanTransferOwnershipResult] -> ShowS
CanTransferOwnershipResult -> String
(I32 -> CanTransferOwnershipResult -> ShowS)
-> (CanTransferOwnershipResult -> String)
-> ([CanTransferOwnershipResult] -> ShowS)
-> Show CanTransferOwnershipResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CanTransferOwnershipResult] -> ShowS
$cshowList :: [CanTransferOwnershipResult] -> ShowS
show :: CanTransferOwnershipResult -> String
$cshow :: CanTransferOwnershipResult -> String
showsPrec :: I32 -> CanTransferOwnershipResult -> ShowS
$cshowsPrec :: I32 -> CanTransferOwnershipResult -> ShowS
Show, CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool
(CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool)
-> (CanTransferOwnershipResult
    -> CanTransferOwnershipResult -> Bool)
-> Eq CanTransferOwnershipResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool
$c/= :: CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool
== :: CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool
$c== :: CanTransferOwnershipResult -> CanTransferOwnershipResult -> Bool
Eq, (forall x.
 CanTransferOwnershipResult -> Rep CanTransferOwnershipResult x)
-> (forall x.
    Rep CanTransferOwnershipResult x -> CanTransferOwnershipResult)
-> Generic CanTransferOwnershipResult
forall x.
Rep CanTransferOwnershipResult x -> CanTransferOwnershipResult
forall x.
CanTransferOwnershipResult -> Rep CanTransferOwnershipResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CanTransferOwnershipResult x -> CanTransferOwnershipResult
$cfrom :: forall x.
CanTransferOwnershipResult -> Rep CanTransferOwnershipResult x
Generic)
-- | Represents result of checking whether a username can be set for a chat
data CheckChatUsernameResult
  = -- | The username can be set
  CheckChatUsernameResultOk
    { 
    }
  | -- | The username is invalid
  CheckChatUsernameResultUsernameInvalid
    { 
    }
  | -- | The username is occupied
  CheckChatUsernameResultUsernameOccupied
    { 
    }
  | -- | The user has too much chats with username, one of them should be made private first
  CheckChatUsernameResultPublicChatsTooMuch
    { 
    }
  | -- | The user can't be a member of a public supergroup
  CheckChatUsernameResultPublicGroupsUnavailable
    { 
    }
  deriving (I32 -> CheckChatUsernameResult -> ShowS
[CheckChatUsernameResult] -> ShowS
CheckChatUsernameResult -> String
(I32 -> CheckChatUsernameResult -> ShowS)
-> (CheckChatUsernameResult -> String)
-> ([CheckChatUsernameResult] -> ShowS)
-> Show CheckChatUsernameResult
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckChatUsernameResult] -> ShowS
$cshowList :: [CheckChatUsernameResult] -> ShowS
show :: CheckChatUsernameResult -> String
$cshow :: CheckChatUsernameResult -> String
showsPrec :: I32 -> CheckChatUsernameResult -> ShowS
$cshowsPrec :: I32 -> CheckChatUsernameResult -> ShowS
Show, CheckChatUsernameResult -> CheckChatUsernameResult -> Bool
(CheckChatUsernameResult -> CheckChatUsernameResult -> Bool)
-> (CheckChatUsernameResult -> CheckChatUsernameResult -> Bool)
-> Eq CheckChatUsernameResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckChatUsernameResult -> CheckChatUsernameResult -> Bool
$c/= :: CheckChatUsernameResult -> CheckChatUsernameResult -> Bool
== :: CheckChatUsernameResult -> CheckChatUsernameResult -> Bool
$c== :: CheckChatUsernameResult -> CheckChatUsernameResult -> Bool
Eq, (forall x.
 CheckChatUsernameResult -> Rep CheckChatUsernameResult x)
-> (forall x.
    Rep CheckChatUsernameResult x -> CheckChatUsernameResult)
-> Generic CheckChatUsernameResult
forall x. Rep CheckChatUsernameResult x -> CheckChatUsernameResult
forall x. CheckChatUsernameResult -> Rep CheckChatUsernameResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckChatUsernameResult x -> CheckChatUsernameResult
$cfrom :: forall x. CheckChatUsernameResult -> Rep CheckChatUsernameResult x
Generic)
-- | Contains content of a push message notification
data PushMessageContent
  = -- | A general message with hidden content 
  PushMessageContentHidden
    { -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_1 :: Bool
    }
  | -- | An animation message (GIF-style). 
  PushMessageContentAnimation
    { -- | Message content; may be null 
      PushMessageContent -> Animation
animation_2 :: Animation,
      -- | Animation caption 
      PushMessageContent -> T
caption_2 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_2 :: Bool
    }
  | -- | An audio message 
  PushMessageContentAudio
    { -- | Message content; may be null 
      PushMessageContent -> Audio
audio_3 :: Audio,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_3 :: Bool
    }
  | -- | A message with a user contact 
  PushMessageContentContact
    { -- | Contact's name 
      PushMessageContent -> T
name_4 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_4 :: Bool
    }
  | -- | A contact has registered with Telegram
  PushMessageContentContactRegistered
    { 
    }
  | -- | A document message (a general file) 
  PushMessageContentDocument
    { -- | Message content; may be null 
      PushMessageContent -> Document
document_6 :: Document,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_6 :: Bool
    }
  | -- | A message with a game 
  PushMessageContentGame
    { -- | Game title, empty for pinned game message 
      PushMessageContent -> T
title_7 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_7 :: Bool
    }
  | -- | A new high score was achieved in a game 
  PushMessageContentGameScore
    { -- | Game title, empty for pinned message 
      PushMessageContent -> T
title_8 :: T,
      -- | New score, 0 for pinned message 
      PushMessageContent -> I32
score_8 :: I32,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_8 :: Bool
    }
  | -- | A message with an invoice from a bot 
  PushMessageContentInvoice
    { -- | Product price 
      PushMessageContent -> T
price_9 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_9 :: Bool
    }
  | -- | A message with a location 
  PushMessageContentLocation
    { -- | True, if the location is live 
      PushMessageContent -> Bool
is_live_10 :: Bool,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_10 :: Bool
    }
  | -- | A photo message 
  PushMessageContentPhoto
    { -- | Message content; may be null 
      PushMessageContent -> Photo
photo_11 :: Photo,
      -- | Photo caption 
      PushMessageContent -> T
caption_11 :: T,
      -- | True, if the photo is secret 
      PushMessageContent -> Bool
is_secret_11 :: Bool,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_11 :: Bool
    }
  | -- | A message with a poll 
  PushMessageContentPoll
    { -- | Poll question 
      PushMessageContent -> T
question_12 :: T,
      -- | True, if the poll is regular and not in quiz mode 
      PushMessageContent -> Bool
is_regular_12 :: Bool,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_12 :: Bool
    }
  | -- | A screenshot of a message in the chat has been taken
  PushMessageContentScreenshotTaken
    { 
    }
  | -- | A message with a sticker 
  PushMessageContentSticker
    { -- | Message content; may be null 
      PushMessageContent -> Sticker
sticker_14 :: Sticker,
      -- | Emoji corresponding to the sticker; may be empty 
      PushMessageContent -> T
emoji_14 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_14 :: Bool
    }
  | -- | A text message 
  PushMessageContentText
    { -- | Message text 
      PushMessageContent -> T
text_15 :: T,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_15 :: Bool
    }
  | -- | A video message 
  PushMessageContentVideo
    { -- | Message content; may be null 
      PushMessageContent -> Video
video_16 :: Video,
      -- | Video caption 
      PushMessageContent -> T
caption_16 :: T,
      -- | True, if the video is secret 
      PushMessageContent -> Bool
is_secret_16 :: Bool,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_16 :: Bool
    }
  | -- | A video note message 
  PushMessageContentVideoNote
    { -- | Message content; may be null 
      PushMessageContent -> VideoNote
video_note_17 :: VideoNote,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_17 :: Bool
    }
  | -- | A voice note message 
  PushMessageContentVoiceNote
    { -- | Message content; may be null 
      PushMessageContent -> VoiceNote
voice_note_18 :: VoiceNote,
      -- | True, if the message is a pinned message with the specified content
      PushMessageContent -> Bool
is_pinned_18 :: Bool
    }
  | -- | A newly created basic group
  PushMessageContentBasicGroupChatCreate
    { 
    }
  | -- | New chat members were invited to a group 
  PushMessageContentChatAddMembers
    { -- | Name of the added member 
      PushMessageContent -> T
member_name_20 :: T,
      -- | True, if the current user was added to the group
      PushMessageContent -> Bool
is_current_user_20 :: Bool,
      -- | True, if the user has returned to the group themself
      PushMessageContent -> Bool
is_returned_20 :: Bool
    }
  | -- | A chat photo was edited
  PushMessageContentChatChangePhoto
    { 
    }
  | -- | A chat title was edited 
  PushMessageContentChatChangeTitle
    { -- | New chat title
      PushMessageContent -> T
title_22 :: T
    }
  | -- | A chat member was deleted 
  PushMessageContentChatDeleteMember
    { -- | Name of the deleted member 
      PushMessageContent -> T
member_name_23 :: T,
      -- | True, if the current user was deleted from the group
      PushMessageContent -> Bool
is_current_user_23 :: Bool,
      -- | True, if the user has left the group themself
      PushMessageContent -> Bool
is_left_23 :: Bool
    }
  | -- | A new member joined the chat by invite link
  PushMessageContentChatJoinByLink
    { 
    }
  | -- | A forwarded messages 
  PushMessageContentMessageForwards
    { -- | Number of forwarded messages
      PushMessageContent -> I32
total_count_25 :: I32
    }
  | -- | A media album 
  PushMessageContentMediaAlbum
    { -- | Number of messages in the album 
      PushMessageContent -> I32
total_count_26 :: I32,
      -- | True, if the album has at least one photo 
      PushMessageContent -> Bool
has_photos_26 :: Bool,
      -- | True, if the album has at least one video
      PushMessageContent -> Bool
has_videos_26 :: Bool
    }
  deriving (I32 -> PushMessageContent -> ShowS
[PushMessageContent] -> ShowS
PushMessageContent -> String
(I32 -> PushMessageContent -> ShowS)
-> (PushMessageContent -> String)
-> ([PushMessageContent] -> ShowS)
-> Show PushMessageContent
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PushMessageContent] -> ShowS
$cshowList :: [PushMessageContent] -> ShowS
show :: PushMessageContent -> String
$cshow :: PushMessageContent -> String
showsPrec :: I32 -> PushMessageContent -> ShowS
$cshowsPrec :: I32 -> PushMessageContent -> ShowS
Show, PushMessageContent -> PushMessageContent -> Bool
(PushMessageContent -> PushMessageContent -> Bool)
-> (PushMessageContent -> PushMessageContent -> Bool)
-> Eq PushMessageContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PushMessageContent -> PushMessageContent -> Bool
$c/= :: PushMessageContent -> PushMessageContent -> Bool
== :: PushMessageContent -> PushMessageContent -> Bool
$c== :: PushMessageContent -> PushMessageContent -> Bool
Eq, (forall x. PushMessageContent -> Rep PushMessageContent x)
-> (forall x. Rep PushMessageContent x -> PushMessageContent)
-> Generic PushMessageContent
forall x. Rep PushMessageContent x -> PushMessageContent
forall x. PushMessageContent -> Rep PushMessageContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PushMessageContent x -> PushMessageContent
$cfrom :: forall x. PushMessageContent -> Rep PushMessageContent x
Generic)
-- | Contains detailed information about a notification
data NotificationType
  = -- | New message was received 
  NotificationTypeNewMessage
    { -- | The message
      NotificationType -> Message
message_1 :: Message
    }
  | -- | New secret chat was created
  NotificationTypeNewSecretChat
    { 
    }
  | -- | New call was received 
  NotificationTypeNewCall
    { -- | Call identifier
      NotificationType -> I32
call_id_3 :: I32
    }
  | -- | New message was received through a push notification
  NotificationTypeNewPushMessage
    { -- | The message identifier. The message will not be available in the chat history, but the ID can be used in viewMessages and as reply_to_message_id
      NotificationType -> I32
message_id_4 :: I53,
      -- | Sender of the message; 0 if unknown. Corresponding user may be inaccessible
      NotificationType -> I32
sender_user_id_4 :: I32,
      -- | Name of the sender; can be different from the name of the sender user
      NotificationType -> T
sender_name_4 :: T,
      -- | True, if the message is outgoing
      NotificationType -> Bool
is_outgoing_4 :: Bool,
      -- | Push message content
      NotificationType -> PushMessageContent
content_4 :: PushMessageContent
    }
  deriving (I32 -> NotificationType -> ShowS
[NotificationType] -> ShowS
NotificationType -> String
(I32 -> NotificationType -> ShowS)
-> (NotificationType -> String)
-> ([NotificationType] -> ShowS)
-> Show NotificationType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationType] -> ShowS
$cshowList :: [NotificationType] -> ShowS
show :: NotificationType -> String
$cshow :: NotificationType -> String
showsPrec :: I32 -> NotificationType -> ShowS
$cshowsPrec :: I32 -> NotificationType -> ShowS
Show, NotificationType -> NotificationType -> Bool
(NotificationType -> NotificationType -> Bool)
-> (NotificationType -> NotificationType -> Bool)
-> Eq NotificationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationType -> NotificationType -> Bool
$c/= :: NotificationType -> NotificationType -> Bool
== :: NotificationType -> NotificationType -> Bool
$c== :: NotificationType -> NotificationType -> Bool
Eq, (forall x. NotificationType -> Rep NotificationType x)
-> (forall x. Rep NotificationType x -> NotificationType)
-> Generic NotificationType
forall x. Rep NotificationType x -> NotificationType
forall x. NotificationType -> Rep NotificationType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotificationType x -> NotificationType
$cfrom :: forall x. NotificationType -> Rep NotificationType x
Generic)
-- | Describes the type of notifications in a notification group
data NotificationGroupType
  = -- | A group containing notifications of type notificationTypeNewMessage and notificationTypeNewPushMessage with ordinary unread messages
  NotificationGroupTypeMessages
    { 
    }
  | -- | A group containing notifications of type notificationTypeNewMessage and notificationTypeNewPushMessage with unread mentions of the current user, replies to their messages, or a pinned message
  NotificationGroupTypeMentions
    { 
    }
  | -- | A group containing a notification of type notificationTypeNewSecretChat
  NotificationGroupTypeSecretChat
    { 
    }
  | -- | A group containing notifications of type notificationTypeNewCall
  NotificationGroupTypeCalls
    { 
    }
  deriving (I32 -> NotificationGroupType -> ShowS
[NotificationGroupType] -> ShowS
NotificationGroupType -> String
(I32 -> NotificationGroupType -> ShowS)
-> (NotificationGroupType -> String)
-> ([NotificationGroupType] -> ShowS)
-> Show NotificationGroupType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationGroupType] -> ShowS
$cshowList :: [NotificationGroupType] -> ShowS
show :: NotificationGroupType -> String
$cshow :: NotificationGroupType -> String
showsPrec :: I32 -> NotificationGroupType -> ShowS
$cshowsPrec :: I32 -> NotificationGroupType -> ShowS
Show, NotificationGroupType -> NotificationGroupType -> Bool
(NotificationGroupType -> NotificationGroupType -> Bool)
-> (NotificationGroupType -> NotificationGroupType -> Bool)
-> Eq NotificationGroupType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationGroupType -> NotificationGroupType -> Bool
$c/= :: NotificationGroupType -> NotificationGroupType -> Bool
== :: NotificationGroupType -> NotificationGroupType -> Bool
$c== :: NotificationGroupType -> NotificationGroupType -> Bool
Eq, (forall x. NotificationGroupType -> Rep NotificationGroupType x)
-> (forall x. Rep NotificationGroupType x -> NotificationGroupType)
-> Generic NotificationGroupType
forall x. Rep NotificationGroupType x -> NotificationGroupType
forall x. NotificationGroupType -> Rep NotificationGroupType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotificationGroupType x -> NotificationGroupType
$cfrom :: forall x. NotificationGroupType -> Rep NotificationGroupType x
Generic)
data Notification
  = -- | Contains information about a notification 
  Notification
    { -- | Unique persistent identifier of this notification 
      Notification -> I32
id_1 :: I32,
      -- | Notification date
      Notification -> I32
date_1 :: I32,
      -- | True, if the notification was initially silent 
      Notification -> Bool
is_silent_1 :: Bool,
      -- | Notification type
      Notification -> NotificationType
type_1 :: NotificationType
    }
  deriving (I32 -> Notification -> ShowS
[Notification] -> ShowS
Notification -> String
(I32 -> Notification -> ShowS)
-> (Notification -> String)
-> ([Notification] -> ShowS)
-> Show Notification
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Notification] -> ShowS
$cshowList :: [Notification] -> ShowS
show :: Notification -> String
$cshow :: Notification -> String
showsPrec :: I32 -> Notification -> ShowS
$cshowsPrec :: I32 -> Notification -> ShowS
Show, Notification -> Notification -> Bool
(Notification -> Notification -> Bool)
-> (Notification -> Notification -> Bool) -> Eq Notification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Notification -> Notification -> Bool
$c/= :: Notification -> Notification -> Bool
== :: Notification -> Notification -> Bool
$c== :: Notification -> Notification -> Bool
Eq, (forall x. Notification -> Rep Notification x)
-> (forall x. Rep Notification x -> Notification)
-> Generic Notification
forall x. Rep Notification x -> Notification
forall x. Notification -> Rep Notification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Notification x -> Notification
$cfrom :: forall x. Notification -> Rep Notification x
Generic)
data NotificationGroup
  = -- | Describes a group of notifications 
  NotificationGroup
    { -- | Unique persistent auto-incremented from 1 identifier of the notification group 
      NotificationGroup -> I32
id_1 :: I32,
      -- | Type of the group
      NotificationGroup -> NotificationGroupType
type_1 :: NotificationGroupType,
      -- | Identifier of a chat to which all notifications in the group belong
      NotificationGroup -> I32
chat_id_1 :: I53,
      -- | Total number of active notifications in the group 
      NotificationGroup -> I32
total_count_1 :: I32,
      -- | The list of active notifications
      NotificationGroup -> [Notification]
notifications_1 :: ([]) (Notification)
    }
  deriving (I32 -> NotificationGroup -> ShowS
[NotificationGroup] -> ShowS
NotificationGroup -> String
(I32 -> NotificationGroup -> ShowS)
-> (NotificationGroup -> String)
-> ([NotificationGroup] -> ShowS)
-> Show NotificationGroup
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NotificationGroup] -> ShowS
$cshowList :: [NotificationGroup] -> ShowS
show :: NotificationGroup -> String
$cshow :: NotificationGroup -> String
showsPrec :: I32 -> NotificationGroup -> ShowS
$cshowsPrec :: I32 -> NotificationGroup -> ShowS
Show, NotificationGroup -> NotificationGroup -> Bool
(NotificationGroup -> NotificationGroup -> Bool)
-> (NotificationGroup -> NotificationGroup -> Bool)
-> Eq NotificationGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NotificationGroup -> NotificationGroup -> Bool
$c/= :: NotificationGroup -> NotificationGroup -> Bool
== :: NotificationGroup -> NotificationGroup -> Bool
$c== :: NotificationGroup -> NotificationGroup -> Bool
Eq, (forall x. NotificationGroup -> Rep NotificationGroup x)
-> (forall x. Rep NotificationGroup x -> NotificationGroup)
-> Generic NotificationGroup
forall x. Rep NotificationGroup x -> NotificationGroup
forall x. NotificationGroup -> Rep NotificationGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NotificationGroup x -> NotificationGroup
$cfrom :: forall x. NotificationGroup -> Rep NotificationGroup x
Generic)
-- | Represents the value of an option
data OptionValue
  = -- | Represents a boolean option 
  OptionValueBoolean
    { -- | The value of the option
      OptionValue -> Bool
value_1 :: Bool
    }
  | -- | Represents an unknown option or an option which has a default value
  OptionValueEmpty
    { 
    }
  | -- | Represents an integer option 
  OptionValueInteger
    { -- | The value of the option
      OptionValue -> I32
value_3 :: I32
    }
  | -- | Represents a string option 
  OptionValueString
    { -- | The value of the option
      OptionValue -> T
value_4 :: T
    }
  deriving (I32 -> OptionValue -> ShowS
[OptionValue] -> ShowS
OptionValue -> String
(I32 -> OptionValue -> ShowS)
-> (OptionValue -> String)
-> ([OptionValue] -> ShowS)
-> Show OptionValue
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptionValue] -> ShowS
$cshowList :: [OptionValue] -> ShowS
show :: OptionValue -> String
$cshow :: OptionValue -> String
showsPrec :: I32 -> OptionValue -> ShowS
$cshowsPrec :: I32 -> OptionValue -> ShowS
Show, OptionValue -> OptionValue -> Bool
(OptionValue -> OptionValue -> Bool)
-> (OptionValue -> OptionValue -> Bool) -> Eq OptionValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptionValue -> OptionValue -> Bool
$c/= :: OptionValue -> OptionValue -> Bool
== :: OptionValue -> OptionValue -> Bool
$c== :: OptionValue -> OptionValue -> Bool
Eq, (forall x. OptionValue -> Rep OptionValue x)
-> (forall x. Rep OptionValue x -> OptionValue)
-> Generic OptionValue
forall x. Rep OptionValue x -> OptionValue
forall x. OptionValue -> Rep OptionValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OptionValue x -> OptionValue
$cfrom :: forall x. OptionValue -> Rep OptionValue x
Generic)
data JsonObjectMember
  = -- | Represents one member of a JSON object 
  JsonObjectMember
    { -- | Member's key 
      JsonObjectMember -> T
key_1 :: T,
      -- | Member's value
      JsonObjectMember -> JsonValue
value_1 :: JsonValue
    }
  deriving (I32 -> JsonObjectMember -> ShowS
[JsonObjectMember] -> ShowS
JsonObjectMember -> String
(I32 -> JsonObjectMember -> ShowS)
-> (JsonObjectMember -> String)
-> ([JsonObjectMember] -> ShowS)
-> Show JsonObjectMember
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JsonObjectMember] -> ShowS
$cshowList :: [JsonObjectMember] -> ShowS
show :: JsonObjectMember -> String
$cshow :: JsonObjectMember -> String
showsPrec :: I32 -> JsonObjectMember -> ShowS
$cshowsPrec :: I32 -> JsonObjectMember -> ShowS
Show, JsonObjectMember -> JsonObjectMember -> Bool
(JsonObjectMember -> JsonObjectMember -> Bool)
-> (JsonObjectMember -> JsonObjectMember -> Bool)
-> Eq JsonObjectMember
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JsonObjectMember -> JsonObjectMember -> Bool
$c/= :: JsonObjectMember -> JsonObjectMember -> Bool
== :: JsonObjectMember -> JsonObjectMember -> Bool
$c== :: JsonObjectMember -> JsonObjectMember -> Bool
Eq, (forall x. JsonObjectMember -> Rep JsonObjectMember x)
-> (forall x. Rep JsonObjectMember x -> JsonObjectMember)
-> Generic JsonObjectMember
forall x. Rep JsonObjectMember x -> JsonObjectMember
forall x. JsonObjectMember -> Rep JsonObjectMember x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JsonObjectMember x -> JsonObjectMember
$cfrom :: forall x. JsonObjectMember -> Rep JsonObjectMember x
Generic)
-- | Represents a JSON value
data JsonValue
  = -- | Represents a null JSON value
  JsonValueNull
    { 
    }
  | -- | Represents a boolean JSON value 
  JsonValueBoolean
    { -- | The value
      JsonValue -> Bool
value_2 :: Bool
    }
  | -- | Represents a numeric JSON value 
  JsonValueNumber
    { -- | The value
      JsonValue -> Double
value_3 :: Double
    }
  | -- | Represents a string JSON value 
  JsonValueString
    { -- | The value
      JsonValue -> T
value_4 :: T
    }
  | -- | Represents a JSON array 
  JsonValueArray
    { -- | The list of array elements
      JsonValue -> [JsonValue]
values_5 :: ([]) (JsonValue)
    }
  | -- | Represents a JSON object 
  JsonValueObject
    { -- | The list of object members
      JsonValue -> [JsonObjectMember]
members_6 :: ([]) (JsonObjectMember)
    }
  deriving (I32 -> JsonValue -> ShowS
[JsonValue] -> ShowS
JsonValue -> String
(I32 -> JsonValue -> ShowS)
-> (JsonValue -> String)
-> ([JsonValue] -> ShowS)
-> Show JsonValue
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JsonValue] -> ShowS
$cshowList :: [JsonValue] -> ShowS
show :: JsonValue -> String
$cshow :: JsonValue -> String
showsPrec :: I32 -> JsonValue -> ShowS
$cshowsPrec :: I32 -> JsonValue -> ShowS
Show, JsonValue -> JsonValue -> Bool
(JsonValue -> JsonValue -> Bool)
-> (JsonValue -> JsonValue -> Bool) -> Eq JsonValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JsonValue -> JsonValue -> Bool
$c/= :: JsonValue -> JsonValue -> Bool
== :: JsonValue -> JsonValue -> Bool
$c== :: JsonValue -> JsonValue -> Bool
Eq, (forall x. JsonValue -> Rep JsonValue x)
-> (forall x. Rep JsonValue x -> JsonValue) -> Generic JsonValue
forall x. Rep JsonValue x -> JsonValue
forall x. JsonValue -> Rep JsonValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JsonValue x -> JsonValue
$cfrom :: forall x. JsonValue -> Rep JsonValue x
Generic)
-- | Represents a single rule for managing privacy settings
data UserPrivacySettingRule
  = -- | A rule to allow all users to do something
  UserPrivacySettingRuleAllowAll
    { 
    }
  | -- | A rule to allow all of a user's contacts to do something
  UserPrivacySettingRuleAllowContacts
    { 
    }
  | -- | A rule to allow certain specified users to do something 
  UserPrivacySettingRuleAllowUsers
    { -- | The user identifiers, total number of users in all rules must not exceed 1000
      UserPrivacySettingRule -> [I32]
user_ids_3 :: ([]) (I32)
    }
  | -- | A rule to allow all members of certain specified basic groups and supergroups to doing something 
  UserPrivacySettingRuleAllowChatMembers
    { -- | The chat identifiers, total number of chats in all rules must not exceed 20
      UserPrivacySettingRule -> [I32]
chat_ids_4 :: ([]) (I53)
    }
  | -- | A rule to restrict all users from doing something
  UserPrivacySettingRuleRestrictAll
    { 
    }
  | -- | A rule to restrict all contacts of a user from doing something
  UserPrivacySettingRuleRestrictContacts
    { 
    }
  | -- | A rule to restrict all specified users from doing something 
  UserPrivacySettingRuleRestrictUsers
    { -- | The user identifiers, total number of users in all rules must not exceed 1000
      UserPrivacySettingRule -> [I32]
user_ids_7 :: ([]) (I32)
    }
  | -- | A rule to restrict all members of specified basic groups and supergroups from doing something 
  UserPrivacySettingRuleRestrictChatMembers
    { -- | The chat identifiers, total number of chats in all rules must not exceed 20
      UserPrivacySettingRule -> [I32]
chat_ids_8 :: ([]) (I53)
    }
  deriving (I32 -> UserPrivacySettingRule -> ShowS
[UserPrivacySettingRule] -> ShowS
UserPrivacySettingRule -> String
(I32 -> UserPrivacySettingRule -> ShowS)
-> (UserPrivacySettingRule -> String)
-> ([UserPrivacySettingRule] -> ShowS)
-> Show UserPrivacySettingRule
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserPrivacySettingRule] -> ShowS
$cshowList :: [UserPrivacySettingRule] -> ShowS
show :: UserPrivacySettingRule -> String
$cshow :: UserPrivacySettingRule -> String
showsPrec :: I32 -> UserPrivacySettingRule -> ShowS
$cshowsPrec :: I32 -> UserPrivacySettingRule -> ShowS
Show, UserPrivacySettingRule -> UserPrivacySettingRule -> Bool
(UserPrivacySettingRule -> UserPrivacySettingRule -> Bool)
-> (UserPrivacySettingRule -> UserPrivacySettingRule -> Bool)
-> Eq UserPrivacySettingRule
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserPrivacySettingRule -> UserPrivacySettingRule -> Bool
$c/= :: UserPrivacySettingRule -> UserPrivacySettingRule -> Bool
== :: UserPrivacySettingRule -> UserPrivacySettingRule -> Bool
$c== :: UserPrivacySettingRule -> UserPrivacySettingRule -> Bool
Eq, (forall x. UserPrivacySettingRule -> Rep UserPrivacySettingRule x)
-> (forall x.
    Rep UserPrivacySettingRule x -> UserPrivacySettingRule)
-> Generic UserPrivacySettingRule
forall x. Rep UserPrivacySettingRule x -> UserPrivacySettingRule
forall x. UserPrivacySettingRule -> Rep UserPrivacySettingRule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserPrivacySettingRule x -> UserPrivacySettingRule
$cfrom :: forall x. UserPrivacySettingRule -> Rep UserPrivacySettingRule x
Generic)
data UserPrivacySettingRules
  = -- | A list of privacy rules. Rules are matched in the specified order. The first matched rule defines the privacy setting for a given user. If no rule matches, the action is not allowed 
  UserPrivacySettingRules
    { -- | A list of rules
      UserPrivacySettingRules -> [UserPrivacySettingRule]
rules_1 :: ([]) (UserPrivacySettingRule)
    }
  deriving (I32 -> UserPrivacySettingRules -> ShowS
[UserPrivacySettingRules] -> ShowS
UserPrivacySettingRules -> String
(I32 -> UserPrivacySettingRules -> ShowS)
-> (UserPrivacySettingRules -> String)
-> ([UserPrivacySettingRules] -> ShowS)
-> Show UserPrivacySettingRules
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserPrivacySettingRules] -> ShowS
$cshowList :: [UserPrivacySettingRules] -> ShowS
show :: UserPrivacySettingRules -> String
$cshow :: UserPrivacySettingRules -> String
showsPrec :: I32 -> UserPrivacySettingRules -> ShowS
$cshowsPrec :: I32 -> UserPrivacySettingRules -> ShowS
Show, UserPrivacySettingRules -> UserPrivacySettingRules -> Bool
(UserPrivacySettingRules -> UserPrivacySettingRules -> Bool)
-> (UserPrivacySettingRules -> UserPrivacySettingRules -> Bool)
-> Eq UserPrivacySettingRules
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserPrivacySettingRules -> UserPrivacySettingRules -> Bool
$c/= :: UserPrivacySettingRules -> UserPrivacySettingRules -> Bool
== :: UserPrivacySettingRules -> UserPrivacySettingRules -> Bool
$c== :: UserPrivacySettingRules -> UserPrivacySettingRules -> Bool
Eq, (forall x.
 UserPrivacySettingRules -> Rep UserPrivacySettingRules x)
-> (forall x.
    Rep UserPrivacySettingRules x -> UserPrivacySettingRules)
-> Generic UserPrivacySettingRules
forall x. Rep UserPrivacySettingRules x -> UserPrivacySettingRules
forall x. UserPrivacySettingRules -> Rep UserPrivacySettingRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserPrivacySettingRules x -> UserPrivacySettingRules
$cfrom :: forall x. UserPrivacySettingRules -> Rep UserPrivacySettingRules x
Generic)
-- | Describes available user privacy settings
data UserPrivacySetting
  = -- | A privacy setting for managing whether the user's online status is visible
  UserPrivacySettingShowStatus
    { 
    }
  | -- | A privacy setting for managing whether the user's profile photo is visible
  UserPrivacySettingShowProfilePhoto
    { 
    }
  | -- | A privacy setting for managing whether a link to the user's account is included in forwarded messages
  UserPrivacySettingShowLinkInForwardedMessages
    { 
    }
  | -- | A privacy setting for managing whether the user's phone number is visible
  UserPrivacySettingShowPhoneNumber
    { 
    }
  | -- | A privacy setting for managing whether the user can be invited to chats
  UserPrivacySettingAllowChatInvites
    { 
    }
  | -- | A privacy setting for managing whether the user can be called
  UserPrivacySettingAllowCalls
    { 
    }
  | -- | A privacy setting for managing whether peer-to-peer connections can be used for calls
  UserPrivacySettingAllowPeerToPeerCalls
    { 
    }
  | -- | A privacy setting for managing whether the user can be found by their phone number. Checked only if the phone number is not known to the other user. Can be set only to "Allow contacts" or "Allow all"
  UserPrivacySettingAllowFindingByPhoneNumber
    { 
    }
  deriving (I32 -> UserPrivacySetting -> ShowS
[UserPrivacySetting] -> ShowS
UserPrivacySetting -> String
(I32 -> UserPrivacySetting -> ShowS)
-> (UserPrivacySetting -> String)
-> ([UserPrivacySetting] -> ShowS)
-> Show UserPrivacySetting
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UserPrivacySetting] -> ShowS
$cshowList :: [UserPrivacySetting] -> ShowS
show :: UserPrivacySetting -> String
$cshow :: UserPrivacySetting -> String
showsPrec :: I32 -> UserPrivacySetting -> ShowS
$cshowsPrec :: I32 -> UserPrivacySetting -> ShowS
Show, UserPrivacySetting -> UserPrivacySetting -> Bool
(UserPrivacySetting -> UserPrivacySetting -> Bool)
-> (UserPrivacySetting -> UserPrivacySetting -> Bool)
-> Eq UserPrivacySetting
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UserPrivacySetting -> UserPrivacySetting -> Bool
$c/= :: UserPrivacySetting -> UserPrivacySetting -> Bool
== :: UserPrivacySetting -> UserPrivacySetting -> Bool
$c== :: UserPrivacySetting -> UserPrivacySetting -> Bool
Eq, (forall x. UserPrivacySetting -> Rep UserPrivacySetting x)
-> (forall x. Rep UserPrivacySetting x -> UserPrivacySetting)
-> Generic UserPrivacySetting
forall x. Rep UserPrivacySetting x -> UserPrivacySetting
forall x. UserPrivacySetting -> Rep UserPrivacySetting x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UserPrivacySetting x -> UserPrivacySetting
$cfrom :: forall x. UserPrivacySetting -> Rep UserPrivacySetting x
Generic)
data AccountTtl
  = -- | Contains information about the period of inactivity after which the current user's account will automatically be deleted 
  AccountTtl
    { -- | Number of days of inactivity before the account will be flagged for deletion; should range from 30-366 days
      AccountTtl -> I32
days_1 :: I32
    }
  deriving (I32 -> AccountTtl -> ShowS
[AccountTtl] -> ShowS
AccountTtl -> String
(I32 -> AccountTtl -> ShowS)
-> (AccountTtl -> String)
-> ([AccountTtl] -> ShowS)
-> Show AccountTtl
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AccountTtl] -> ShowS
$cshowList :: [AccountTtl] -> ShowS
show :: AccountTtl -> String
$cshow :: AccountTtl -> String
showsPrec :: I32 -> AccountTtl -> ShowS
$cshowsPrec :: I32 -> AccountTtl -> ShowS
Show, AccountTtl -> AccountTtl -> Bool
(AccountTtl -> AccountTtl -> Bool)
-> (AccountTtl -> AccountTtl -> Bool) -> Eq AccountTtl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AccountTtl -> AccountTtl -> Bool
$c/= :: AccountTtl -> AccountTtl -> Bool
== :: AccountTtl -> AccountTtl -> Bool
$c== :: AccountTtl -> AccountTtl -> Bool
Eq, (forall x. AccountTtl -> Rep AccountTtl x)
-> (forall x. Rep AccountTtl x -> AccountTtl) -> Generic AccountTtl
forall x. Rep AccountTtl x -> AccountTtl
forall x. AccountTtl -> Rep AccountTtl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AccountTtl x -> AccountTtl
$cfrom :: forall x. AccountTtl -> Rep AccountTtl x
Generic)
data Session
  = -- | Contains information about one session in a Telegram application used by the current user. Sessions should be shown to the user in the returned order
  Session
    { -- | Session identifier 
      Session -> I64
id_1 :: I64,
      -- | True, if this session is the current session
      Session -> Bool
is_current_1 :: Bool,
      -- | True, if a password is needed to complete authorization of the session
      Session -> Bool
is_password_pending_1 :: Bool,
      -- | Telegram API identifier, as provided by the application 
      Session -> I32
api_id_1 :: I32,
      -- | Name of the application, as provided by the application
      Session -> T
application_name_1 :: T,
      -- | The version of the application, as provided by the application 
      Session -> T
application_version_1 :: T,
      -- | True, if the application is an official application or uses the api_id of an official application
      Session -> Bool
is_official_application_1 :: Bool,
      -- | Model of the device the application has been run or is running on, as provided by the application 
      Session -> T
device_model_1 :: T,
      -- | Operating system the application has been run or is running on, as provided by the application
      Session -> T
platform_1 :: T,
      -- | Version of the operating system the application has been run or is running on, as provided by the application 
      Session -> T
system_version_1 :: T,
      -- | Point in time (Unix timestamp) when the user has logged in
      Session -> I32
log_in_date_1 :: I32,
      -- | Point in time (Unix timestamp) when the session was last used 
      Session -> I32
last_active_date_1 :: I32,
      -- | IP address from which the session was created, in human-readable format
      Session -> T
ip_1 :: T,
      -- | A two-letter country code for the country from which the session was created, based on the IP address 
      Session -> T
country_1 :: T,
      -- | Region code from which the session was created, based on the IP address
      Session -> T
region_1 :: T
    }
  deriving (I32 -> Session -> ShowS
[Session] -> ShowS
Session -> String
(I32 -> Session -> ShowS)
-> (Session -> String) -> ([Session] -> ShowS) -> Show Session
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Session] -> ShowS
$cshowList :: [Session] -> ShowS
show :: Session -> String
$cshow :: Session -> String
showsPrec :: I32 -> Session -> ShowS
$cshowsPrec :: I32 -> Session -> ShowS
Show, Session -> Session -> Bool
(Session -> Session -> Bool)
-> (Session -> Session -> Bool) -> Eq Session
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Session -> Session -> Bool
$c/= :: Session -> Session -> Bool
== :: Session -> Session -> Bool
$c== :: Session -> Session -> Bool
Eq, (forall x. Session -> Rep Session x)
-> (forall x. Rep Session x -> Session) -> Generic Session
forall x. Rep Session x -> Session
forall x. Session -> Rep Session x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Session x -> Session
$cfrom :: forall x. Session -> Rep Session x
Generic)
data Sessions
  = -- | Contains a list of sessions 
  Sessions
    { -- | List of sessions
      Sessions -> [Session]
sessions_1 :: ([]) (Session)
    }
  deriving (I32 -> Sessions -> ShowS
[Sessions] -> ShowS
Sessions -> String
(I32 -> Sessions -> ShowS)
-> (Sessions -> String) -> ([Sessions] -> ShowS) -> Show Sessions
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Sessions] -> ShowS
$cshowList :: [Sessions] -> ShowS
show :: Sessions -> String
$cshow :: Sessions -> String
showsPrec :: I32 -> Sessions -> ShowS
$cshowsPrec :: I32 -> Sessions -> ShowS
Show, Sessions -> Sessions -> Bool
(Sessions -> Sessions -> Bool)
-> (Sessions -> Sessions -> Bool) -> Eq Sessions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Sessions -> Sessions -> Bool
$c/= :: Sessions -> Sessions -> Bool
== :: Sessions -> Sessions -> Bool
$c== :: Sessions -> Sessions -> Bool
Eq, (forall x. Sessions -> Rep Sessions x)
-> (forall x. Rep Sessions x -> Sessions) -> Generic Sessions
forall x. Rep Sessions x -> Sessions
forall x. Sessions -> Rep Sessions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Sessions x -> Sessions
$cfrom :: forall x. Sessions -> Rep Sessions x
Generic)
data ConnectedWebsite
  = -- | Contains information about one website the current user is logged in with Telegram
  ConnectedWebsite
    { -- | Website identifier
      ConnectedWebsite -> I64
id_1 :: I64,
      -- | The domain name of the website
      ConnectedWebsite -> T
domain_name_1 :: T,
      -- | User identifier of a bot linked with the website
      ConnectedWebsite -> I32
bot_user_id_1 :: I32,
      -- | The version of a browser used to log in
      ConnectedWebsite -> T
browser_1 :: T,
      -- | Operating system the browser is running on
      ConnectedWebsite -> T
platform_1 :: T,
      -- | Point in time (Unix timestamp) when the user was logged in
      ConnectedWebsite -> I32
log_in_date_1 :: I32,
      -- | Point in time (Unix timestamp) when obtained authorization was last used
      ConnectedWebsite -> I32
last_active_date_1 :: I32,
      -- | IP address from which the user was logged in, in human-readable format
      ConnectedWebsite -> T
ip_1 :: T,
      -- | Human-readable description of a country and a region, from which the user was logged in, based on the IP address
      ConnectedWebsite -> T
location_1 :: T
    }
  deriving (I32 -> ConnectedWebsite -> ShowS
[ConnectedWebsite] -> ShowS
ConnectedWebsite -> String
(I32 -> ConnectedWebsite -> ShowS)
-> (ConnectedWebsite -> String)
-> ([ConnectedWebsite] -> ShowS)
-> Show ConnectedWebsite
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectedWebsite] -> ShowS
$cshowList :: [ConnectedWebsite] -> ShowS
show :: ConnectedWebsite -> String
$cshow :: ConnectedWebsite -> String
showsPrec :: I32 -> ConnectedWebsite -> ShowS
$cshowsPrec :: I32 -> ConnectedWebsite -> ShowS
Show, ConnectedWebsite -> ConnectedWebsite -> Bool
(ConnectedWebsite -> ConnectedWebsite -> Bool)
-> (ConnectedWebsite -> ConnectedWebsite -> Bool)
-> Eq ConnectedWebsite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectedWebsite -> ConnectedWebsite -> Bool
$c/= :: ConnectedWebsite -> ConnectedWebsite -> Bool
== :: ConnectedWebsite -> ConnectedWebsite -> Bool
$c== :: ConnectedWebsite -> ConnectedWebsite -> Bool
Eq, (forall x. ConnectedWebsite -> Rep ConnectedWebsite x)
-> (forall x. Rep ConnectedWebsite x -> ConnectedWebsite)
-> Generic ConnectedWebsite
forall x. Rep ConnectedWebsite x -> ConnectedWebsite
forall x. ConnectedWebsite -> Rep ConnectedWebsite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectedWebsite x -> ConnectedWebsite
$cfrom :: forall x. ConnectedWebsite -> Rep ConnectedWebsite x
Generic)
data ConnectedWebsites
  = -- | Contains a list of websites the current user is logged in with Telegram 
  ConnectedWebsites
    { -- | List of connected websites
      ConnectedWebsites -> [ConnectedWebsite]
websites_1 :: ([]) (ConnectedWebsite)
    }
  deriving (I32 -> ConnectedWebsites -> ShowS
[ConnectedWebsites] -> ShowS
ConnectedWebsites -> String
(I32 -> ConnectedWebsites -> ShowS)
-> (ConnectedWebsites -> String)
-> ([ConnectedWebsites] -> ShowS)
-> Show ConnectedWebsites
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectedWebsites] -> ShowS
$cshowList :: [ConnectedWebsites] -> ShowS
show :: ConnectedWebsites -> String
$cshow :: ConnectedWebsites -> String
showsPrec :: I32 -> ConnectedWebsites -> ShowS
$cshowsPrec :: I32 -> ConnectedWebsites -> ShowS
Show, ConnectedWebsites -> ConnectedWebsites -> Bool
(ConnectedWebsites -> ConnectedWebsites -> Bool)
-> (ConnectedWebsites -> ConnectedWebsites -> Bool)
-> Eq ConnectedWebsites
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectedWebsites -> ConnectedWebsites -> Bool
$c/= :: ConnectedWebsites -> ConnectedWebsites -> Bool
== :: ConnectedWebsites -> ConnectedWebsites -> Bool
$c== :: ConnectedWebsites -> ConnectedWebsites -> Bool
Eq, (forall x. ConnectedWebsites -> Rep ConnectedWebsites x)
-> (forall x. Rep ConnectedWebsites x -> ConnectedWebsites)
-> Generic ConnectedWebsites
forall x. Rep ConnectedWebsites x -> ConnectedWebsites
forall x. ConnectedWebsites -> Rep ConnectedWebsites x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectedWebsites x -> ConnectedWebsites
$cfrom :: forall x. ConnectedWebsites -> Rep ConnectedWebsites x
Generic)
-- | Describes the reason why a chat is reported
data ChatReportReason
  = -- | The chat contains spam messages
  ChatReportReasonSpam
    { 
    }
  | -- | The chat promotes violence
  ChatReportReasonViolence
    { 
    }
  | -- | The chat contains pornographic messages
  ChatReportReasonPornography
    { 
    }
  | -- | The chat has child abuse related content
  ChatReportReasonChildAbuse
    { 
    }
  | -- | The chat contains copyrighted content
  ChatReportReasonCopyright
    { 
    }
  | -- | The location-based chat is unrelated to its stated location
  ChatReportReasonUnrelatedLocation
    { 
    }
  | -- | A custom reason provided by the user 
  ChatReportReasonCustom
    { -- | Report text
      ChatReportReason -> T
text_7 :: T
    }
  deriving (I32 -> ChatReportReason -> ShowS
[ChatReportReason] -> ShowS
ChatReportReason -> String
(I32 -> ChatReportReason -> ShowS)
-> (ChatReportReason -> String)
-> ([ChatReportReason] -> ShowS)
-> Show ChatReportReason
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatReportReason] -> ShowS
$cshowList :: [ChatReportReason] -> ShowS
show :: ChatReportReason -> String
$cshow :: ChatReportReason -> String
showsPrec :: I32 -> ChatReportReason -> ShowS
$cshowsPrec :: I32 -> ChatReportReason -> ShowS
Show, ChatReportReason -> ChatReportReason -> Bool
(ChatReportReason -> ChatReportReason -> Bool)
-> (ChatReportReason -> ChatReportReason -> Bool)
-> Eq ChatReportReason
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatReportReason -> ChatReportReason -> Bool
$c/= :: ChatReportReason -> ChatReportReason -> Bool
== :: ChatReportReason -> ChatReportReason -> Bool
$c== :: ChatReportReason -> ChatReportReason -> Bool
Eq, (forall x. ChatReportReason -> Rep ChatReportReason x)
-> (forall x. Rep ChatReportReason x -> ChatReportReason)
-> Generic ChatReportReason
forall x. Rep ChatReportReason x -> ChatReportReason
forall x. ChatReportReason -> Rep ChatReportReason x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatReportReason x -> ChatReportReason
$cfrom :: forall x. ChatReportReason -> Rep ChatReportReason x
Generic)
data PublicMessageLink
  = -- | Contains a public HTTPS link to a message in a supergroup or channel with a username 
  PublicMessageLink
    { -- | Message link 
      PublicMessageLink -> T
link_1 :: T,
      -- | HTML-code for embedding the message
      PublicMessageLink -> T
html_1 :: T
    }
  deriving (I32 -> PublicMessageLink -> ShowS
[PublicMessageLink] -> ShowS
PublicMessageLink -> String
(I32 -> PublicMessageLink -> ShowS)
-> (PublicMessageLink -> String)
-> ([PublicMessageLink] -> ShowS)
-> Show PublicMessageLink
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublicMessageLink] -> ShowS
$cshowList :: [PublicMessageLink] -> ShowS
show :: PublicMessageLink -> String
$cshow :: PublicMessageLink -> String
showsPrec :: I32 -> PublicMessageLink -> ShowS
$cshowsPrec :: I32 -> PublicMessageLink -> ShowS
Show, PublicMessageLink -> PublicMessageLink -> Bool
(PublicMessageLink -> PublicMessageLink -> Bool)
-> (PublicMessageLink -> PublicMessageLink -> Bool)
-> Eq PublicMessageLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublicMessageLink -> PublicMessageLink -> Bool
$c/= :: PublicMessageLink -> PublicMessageLink -> Bool
== :: PublicMessageLink -> PublicMessageLink -> Bool
$c== :: PublicMessageLink -> PublicMessageLink -> Bool
Eq, (forall x. PublicMessageLink -> Rep PublicMessageLink x)
-> (forall x. Rep PublicMessageLink x -> PublicMessageLink)
-> Generic PublicMessageLink
forall x. Rep PublicMessageLink x -> PublicMessageLink
forall x. PublicMessageLink -> Rep PublicMessageLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublicMessageLink x -> PublicMessageLink
$cfrom :: forall x. PublicMessageLink -> Rep PublicMessageLink x
Generic)
data MessageLinkInfo
  = -- | Contains information about a link to a message in a chat
  MessageLinkInfo
    { -- | True, if the link is a public link for a message in a chat
      MessageLinkInfo -> Bool
is_public_1 :: Bool,
      -- | If found, identifier of the chat to which the message belongs, 0 otherwise
      MessageLinkInfo -> I32
chat_id_1 :: I53,
      -- | If found, the linked message; may be null
      MessageLinkInfo -> Message
message_1 :: Message,
      -- | True, if the whole media album to which the message belongs is linked
      MessageLinkInfo -> Bool
for_album_1 :: Bool
    }
  deriving (I32 -> MessageLinkInfo -> ShowS
[MessageLinkInfo] -> ShowS
MessageLinkInfo -> String
(I32 -> MessageLinkInfo -> ShowS)
-> (MessageLinkInfo -> String)
-> ([MessageLinkInfo] -> ShowS)
-> Show MessageLinkInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageLinkInfo] -> ShowS
$cshowList :: [MessageLinkInfo] -> ShowS
show :: MessageLinkInfo -> String
$cshow :: MessageLinkInfo -> String
showsPrec :: I32 -> MessageLinkInfo -> ShowS
$cshowsPrec :: I32 -> MessageLinkInfo -> ShowS
Show, MessageLinkInfo -> MessageLinkInfo -> Bool
(MessageLinkInfo -> MessageLinkInfo -> Bool)
-> (MessageLinkInfo -> MessageLinkInfo -> Bool)
-> Eq MessageLinkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageLinkInfo -> MessageLinkInfo -> Bool
$c/= :: MessageLinkInfo -> MessageLinkInfo -> Bool
== :: MessageLinkInfo -> MessageLinkInfo -> Bool
$c== :: MessageLinkInfo -> MessageLinkInfo -> Bool
Eq, (forall x. MessageLinkInfo -> Rep MessageLinkInfo x)
-> (forall x. Rep MessageLinkInfo x -> MessageLinkInfo)
-> Generic MessageLinkInfo
forall x. Rep MessageLinkInfo x -> MessageLinkInfo
forall x. MessageLinkInfo -> Rep MessageLinkInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep MessageLinkInfo x -> MessageLinkInfo
$cfrom :: forall x. MessageLinkInfo -> Rep MessageLinkInfo x
Generic)
data FilePart
  = -- | Contains a part of a file 
  FilePart
    { -- | File bytes
      FilePart -> ByteString64
data_1 :: ByteString64
    }
  deriving (I32 -> FilePart -> ShowS
[FilePart] -> ShowS
FilePart -> String
(I32 -> FilePart -> ShowS)
-> (FilePart -> String) -> ([FilePart] -> ShowS) -> Show FilePart
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FilePart] -> ShowS
$cshowList :: [FilePart] -> ShowS
show :: FilePart -> String
$cshow :: FilePart -> String
showsPrec :: I32 -> FilePart -> ShowS
$cshowsPrec :: I32 -> FilePart -> ShowS
Show, FilePart -> FilePart -> Bool
(FilePart -> FilePart -> Bool)
-> (FilePart -> FilePart -> Bool) -> Eq FilePart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilePart -> FilePart -> Bool
$c/= :: FilePart -> FilePart -> Bool
== :: FilePart -> FilePart -> Bool
$c== :: FilePart -> FilePart -> Bool
Eq, (forall x. FilePart -> Rep FilePart x)
-> (forall x. Rep FilePart x -> FilePart) -> Generic FilePart
forall x. Rep FilePart x -> FilePart
forall x. FilePart -> Rep FilePart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilePart x -> FilePart
$cfrom :: forall x. FilePart -> Rep FilePart x
Generic)
-- | Represents the type of a file
data FileType
  = -- | The data is not a file
  FileTypeNone
    { 
    }
  | -- | The file is an animation
  FileTypeAnimation
    { 
    }
  | -- | The file is an audio file
  FileTypeAudio
    { 
    }
  | -- | The file is a document
  FileTypeDocument
    { 
    }
  | -- | The file is a photo
  FileTypePhoto
    { 
    }
  | -- | The file is a profile photo
  FileTypeProfilePhoto
    { 
    }
  | -- | The file was sent to a secret chat (the file type is not known to the server)
  FileTypeSecret
    { 
    }
  | -- | The file is a thumbnail of a file from a secret chat
  FileTypeSecretThumbnail
    { 
    }
  | -- | The file is a file from Secure storage used for storing Telegram Passport files
  FileTypeSecure
    { 
    }
  | -- | The file is a sticker
  FileTypeSticker
    { 
    }
  | -- | The file is a thumbnail of another file
  FileTypeThumbnail
    { 
    }
  | -- | The file type is not yet known
  FileTypeUnknown
    { 
    }
  | -- | The file is a video
  FileTypeVideo
    { 
    }
  | -- | The file is a video note
  FileTypeVideoNote
    { 
    }
  | -- | The file is a voice note
  FileTypeVoiceNote
    { 
    }
  | -- | The file is a wallpaper or a background pattern
  FileTypeWallpaper
    { 
    }
  deriving (I32 -> FileType -> ShowS
[FileType] -> ShowS
FileType -> String
(I32 -> FileType -> ShowS)
-> (FileType -> String) -> ([FileType] -> ShowS) -> Show FileType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FileType] -> ShowS
$cshowList :: [FileType] -> ShowS
show :: FileType -> String
$cshow :: FileType -> String
showsPrec :: I32 -> FileType -> ShowS
$cshowsPrec :: I32 -> FileType -> ShowS
Show, FileType -> FileType -> Bool
(FileType -> FileType -> Bool)
-> (FileType -> FileType -> Bool) -> Eq FileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FileType -> FileType -> Bool
$c/= :: FileType -> FileType -> Bool
== :: FileType -> FileType -> Bool
$c== :: FileType -> FileType -> Bool
Eq, (forall x. FileType -> Rep FileType x)
-> (forall x. Rep FileType x -> FileType) -> Generic FileType
forall x. Rep FileType x -> FileType
forall x. FileType -> Rep FileType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FileType x -> FileType
$cfrom :: forall x. FileType -> Rep FileType x
Generic)
data StorageStatisticsByFileType
  = -- | Contains the storage usage statistics for a specific file type 
  StorageStatisticsByFileType
    { -- | File type 
      StorageStatisticsByFileType -> FileType
file_type_1 :: FileType,
      -- | Total size of the files 
      StorageStatisticsByFileType -> I32
size_1 :: I53,
      -- | Total number of files
      StorageStatisticsByFileType -> I32
count_1 :: I32
    }
  deriving (I32 -> StorageStatisticsByFileType -> ShowS
[StorageStatisticsByFileType] -> ShowS
StorageStatisticsByFileType -> String
(I32 -> StorageStatisticsByFileType -> ShowS)
-> (StorageStatisticsByFileType -> String)
-> ([StorageStatisticsByFileType] -> ShowS)
-> Show StorageStatisticsByFileType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StorageStatisticsByFileType] -> ShowS
$cshowList :: [StorageStatisticsByFileType] -> ShowS
show :: StorageStatisticsByFileType -> String
$cshow :: StorageStatisticsByFileType -> String
showsPrec :: I32 -> StorageStatisticsByFileType -> ShowS
$cshowsPrec :: I32 -> StorageStatisticsByFileType -> ShowS
Show, StorageStatisticsByFileType -> StorageStatisticsByFileType -> Bool
(StorageStatisticsByFileType
 -> StorageStatisticsByFileType -> Bool)
-> (StorageStatisticsByFileType
    -> StorageStatisticsByFileType -> Bool)
-> Eq StorageStatisticsByFileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StorageStatisticsByFileType -> StorageStatisticsByFileType -> Bool
$c/= :: StorageStatisticsByFileType -> StorageStatisticsByFileType -> Bool
== :: StorageStatisticsByFileType -> StorageStatisticsByFileType -> Bool
$c== :: StorageStatisticsByFileType -> StorageStatisticsByFileType -> Bool
Eq, (forall x.
 StorageStatisticsByFileType -> Rep StorageStatisticsByFileType x)
-> (forall x.
    Rep StorageStatisticsByFileType x -> StorageStatisticsByFileType)
-> Generic StorageStatisticsByFileType
forall x.
Rep StorageStatisticsByFileType x -> StorageStatisticsByFileType
forall x.
StorageStatisticsByFileType -> Rep StorageStatisticsByFileType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StorageStatisticsByFileType x -> StorageStatisticsByFileType
$cfrom :: forall x.
StorageStatisticsByFileType -> Rep StorageStatisticsByFileType x
Generic)
data StorageStatisticsByChat
  = -- | Contains the storage usage statistics for a specific chat 
  StorageStatisticsByChat
    { -- | Chat identifier; 0 if none 
      StorageStatisticsByChat -> I32
chat_id_1 :: I53,
      -- | Total size of the files in the chat 
      StorageStatisticsByChat -> I32
size_1 :: I53,
      -- | Total number of files in the chat 
      StorageStatisticsByChat -> I32
count_1 :: I32,
      -- | Statistics split by file types
      StorageStatisticsByChat -> [StorageStatisticsByFileType]
by_file_type_1 :: ([]) (StorageStatisticsByFileType)
    }
  deriving (I32 -> StorageStatisticsByChat -> ShowS
[StorageStatisticsByChat] -> ShowS
StorageStatisticsByChat -> String
(I32 -> StorageStatisticsByChat -> ShowS)
-> (StorageStatisticsByChat -> String)
-> ([StorageStatisticsByChat] -> ShowS)
-> Show StorageStatisticsByChat
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StorageStatisticsByChat] -> ShowS
$cshowList :: [StorageStatisticsByChat] -> ShowS
show :: StorageStatisticsByChat -> String
$cshow :: StorageStatisticsByChat -> String
showsPrec :: I32 -> StorageStatisticsByChat -> ShowS
$cshowsPrec :: I32 -> StorageStatisticsByChat -> ShowS
Show, StorageStatisticsByChat -> StorageStatisticsByChat -> Bool
(StorageStatisticsByChat -> StorageStatisticsByChat -> Bool)
-> (StorageStatisticsByChat -> StorageStatisticsByChat -> Bool)
-> Eq StorageStatisticsByChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StorageStatisticsByChat -> StorageStatisticsByChat -> Bool
$c/= :: StorageStatisticsByChat -> StorageStatisticsByChat -> Bool
== :: StorageStatisticsByChat -> StorageStatisticsByChat -> Bool
$c== :: StorageStatisticsByChat -> StorageStatisticsByChat -> Bool
Eq, (forall x.
 StorageStatisticsByChat -> Rep StorageStatisticsByChat x)
-> (forall x.
    Rep StorageStatisticsByChat x -> StorageStatisticsByChat)
-> Generic StorageStatisticsByChat
forall x. Rep StorageStatisticsByChat x -> StorageStatisticsByChat
forall x. StorageStatisticsByChat -> Rep StorageStatisticsByChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StorageStatisticsByChat x -> StorageStatisticsByChat
$cfrom :: forall x. StorageStatisticsByChat -> Rep StorageStatisticsByChat x
Generic)
data StorageStatistics
  = -- | Contains the exact storage usage statistics split by chats and file type 
  StorageStatistics
    { -- | Total size of files 
      StorageStatistics -> I32
size_1 :: I53,
      -- | Total number of files 
      StorageStatistics -> I32
count_1 :: I32,
      -- | Statistics split by chats
      StorageStatistics -> [StorageStatisticsByChat]
by_chat_1 :: ([]) (StorageStatisticsByChat)
    }
  deriving (I32 -> StorageStatistics -> ShowS
[StorageStatistics] -> ShowS
StorageStatistics -> String
(I32 -> StorageStatistics -> ShowS)
-> (StorageStatistics -> String)
-> ([StorageStatistics] -> ShowS)
-> Show StorageStatistics
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StorageStatistics] -> ShowS
$cshowList :: [StorageStatistics] -> ShowS
show :: StorageStatistics -> String
$cshow :: StorageStatistics -> String
showsPrec :: I32 -> StorageStatistics -> ShowS
$cshowsPrec :: I32 -> StorageStatistics -> ShowS
Show, StorageStatistics -> StorageStatistics -> Bool
(StorageStatistics -> StorageStatistics -> Bool)
-> (StorageStatistics -> StorageStatistics -> Bool)
-> Eq StorageStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StorageStatistics -> StorageStatistics -> Bool
$c/= :: StorageStatistics -> StorageStatistics -> Bool
== :: StorageStatistics -> StorageStatistics -> Bool
$c== :: StorageStatistics -> StorageStatistics -> Bool
Eq, (forall x. StorageStatistics -> Rep StorageStatistics x)
-> (forall x. Rep StorageStatistics x -> StorageStatistics)
-> Generic StorageStatistics
forall x. Rep StorageStatistics x -> StorageStatistics
forall x. StorageStatistics -> Rep StorageStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StorageStatistics x -> StorageStatistics
$cfrom :: forall x. StorageStatistics -> Rep StorageStatistics x
Generic)
data StorageStatisticsFast
  = -- | Contains approximate storage usage statistics, excluding files of unknown file type 
  StorageStatisticsFast
    { -- | Approximate total size of files 
      StorageStatisticsFast -> I32
files_size_1 :: I53,
      -- | Approximate number of files
      StorageStatisticsFast -> I32
file_count_1 :: I32,
      -- | Size of the database 
      StorageStatisticsFast -> I32
database_size_1 :: I53,
      -- | Size of the language pack database 
      StorageStatisticsFast -> I32
language_pack_database_size_1 :: I53,
      -- | Size of the TDLib internal log
      StorageStatisticsFast -> I32
log_size_1 :: I53
    }
  deriving (I32 -> StorageStatisticsFast -> ShowS
[StorageStatisticsFast] -> ShowS
StorageStatisticsFast -> String
(I32 -> StorageStatisticsFast -> ShowS)
-> (StorageStatisticsFast -> String)
-> ([StorageStatisticsFast] -> ShowS)
-> Show StorageStatisticsFast
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StorageStatisticsFast] -> ShowS
$cshowList :: [StorageStatisticsFast] -> ShowS
show :: StorageStatisticsFast -> String
$cshow :: StorageStatisticsFast -> String
showsPrec :: I32 -> StorageStatisticsFast -> ShowS
$cshowsPrec :: I32 -> StorageStatisticsFast -> ShowS
Show, StorageStatisticsFast -> StorageStatisticsFast -> Bool
(StorageStatisticsFast -> StorageStatisticsFast -> Bool)
-> (StorageStatisticsFast -> StorageStatisticsFast -> Bool)
-> Eq StorageStatisticsFast
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StorageStatisticsFast -> StorageStatisticsFast -> Bool
$c/= :: StorageStatisticsFast -> StorageStatisticsFast -> Bool
== :: StorageStatisticsFast -> StorageStatisticsFast -> Bool
$c== :: StorageStatisticsFast -> StorageStatisticsFast -> Bool
Eq, (forall x. StorageStatisticsFast -> Rep StorageStatisticsFast x)
-> (forall x. Rep StorageStatisticsFast x -> StorageStatisticsFast)
-> Generic StorageStatisticsFast
forall x. Rep StorageStatisticsFast x -> StorageStatisticsFast
forall x. StorageStatisticsFast -> Rep StorageStatisticsFast x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StorageStatisticsFast x -> StorageStatisticsFast
$cfrom :: forall x. StorageStatisticsFast -> Rep StorageStatisticsFast x
Generic)
data DatabaseStatistics
  = -- | Contains database statistics
  DatabaseStatistics
    { -- | Database statistics in an unspecified human-readable format
      DatabaseStatistics -> T
statistics_1 :: T
    }
  deriving (I32 -> DatabaseStatistics -> ShowS
[DatabaseStatistics] -> ShowS
DatabaseStatistics -> String
(I32 -> DatabaseStatistics -> ShowS)
-> (DatabaseStatistics -> String)
-> ([DatabaseStatistics] -> ShowS)
-> Show DatabaseStatistics
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatabaseStatistics] -> ShowS
$cshowList :: [DatabaseStatistics] -> ShowS
show :: DatabaseStatistics -> String
$cshow :: DatabaseStatistics -> String
showsPrec :: I32 -> DatabaseStatistics -> ShowS
$cshowsPrec :: I32 -> DatabaseStatistics -> ShowS
Show, DatabaseStatistics -> DatabaseStatistics -> Bool
(DatabaseStatistics -> DatabaseStatistics -> Bool)
-> (DatabaseStatistics -> DatabaseStatistics -> Bool)
-> Eq DatabaseStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatabaseStatistics -> DatabaseStatistics -> Bool
$c/= :: DatabaseStatistics -> DatabaseStatistics -> Bool
== :: DatabaseStatistics -> DatabaseStatistics -> Bool
$c== :: DatabaseStatistics -> DatabaseStatistics -> Bool
Eq, (forall x. DatabaseStatistics -> Rep DatabaseStatistics x)
-> (forall x. Rep DatabaseStatistics x -> DatabaseStatistics)
-> Generic DatabaseStatistics
forall x. Rep DatabaseStatistics x -> DatabaseStatistics
forall x. DatabaseStatistics -> Rep DatabaseStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatabaseStatistics x -> DatabaseStatistics
$cfrom :: forall x. DatabaseStatistics -> Rep DatabaseStatistics x
Generic)
-- | Represents the type of a network
data NetworkType
  = -- | The network is not available
  NetworkTypeNone
    { 
    }
  | -- | A mobile network
  NetworkTypeMobile
    { 
    }
  | -- | A mobile roaming network
  NetworkTypeMobileRoaming
    { 
    }
  | -- | A Wi-Fi network
  NetworkTypeWiFi
    { 
    }
  | -- | A different network type (e.g., Ethernet network)
  NetworkTypeOther
    { 
    }
  deriving (I32 -> NetworkType -> ShowS
[NetworkType] -> ShowS
NetworkType -> String
(I32 -> NetworkType -> ShowS)
-> (NetworkType -> String)
-> ([NetworkType] -> ShowS)
-> Show NetworkType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkType] -> ShowS
$cshowList :: [NetworkType] -> ShowS
show :: NetworkType -> String
$cshow :: NetworkType -> String
showsPrec :: I32 -> NetworkType -> ShowS
$cshowsPrec :: I32 -> NetworkType -> ShowS
Show, NetworkType -> NetworkType -> Bool
(NetworkType -> NetworkType -> Bool)
-> (NetworkType -> NetworkType -> Bool) -> Eq NetworkType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkType -> NetworkType -> Bool
$c/= :: NetworkType -> NetworkType -> Bool
== :: NetworkType -> NetworkType -> Bool
$c== :: NetworkType -> NetworkType -> Bool
Eq, (forall x. NetworkType -> Rep NetworkType x)
-> (forall x. Rep NetworkType x -> NetworkType)
-> Generic NetworkType
forall x. Rep NetworkType x -> NetworkType
forall x. NetworkType -> Rep NetworkType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetworkType x -> NetworkType
$cfrom :: forall x. NetworkType -> Rep NetworkType x
Generic)
-- | Contains statistics about network usage
data NetworkStatisticsEntry
  = -- | Contains information about the total amount of data that was used to send and receive files 
  NetworkStatisticsEntryFile
    { -- | Type of the file the data is part of 
      NetworkStatisticsEntry -> FileType
file_type_1 :: FileType,
      -- | Type of the network the data was sent through. Call setNetworkType to maintain the actual network type
      NetworkStatisticsEntry -> NetworkType
network_type_1 :: NetworkType,
      -- | Total number of bytes sent 
      NetworkStatisticsEntry -> I32
sent_bytes_1 :: I53,
      -- | Total number of bytes received
      NetworkStatisticsEntry -> I32
received_bytes_1 :: I53
    }
  | -- | Contains information about the total amount of data that was used for calls 
  NetworkStatisticsEntryCall
    { -- | Type of the network the data was sent through. Call setNetworkType to maintain the actual network type
      NetworkStatisticsEntry -> NetworkType
network_type_2 :: NetworkType,
      -- | Total number of bytes sent 
      NetworkStatisticsEntry -> I32
sent_bytes_2 :: I53,
      -- | Total number of bytes received 
      NetworkStatisticsEntry -> I32
received_bytes_2 :: I53,
      -- | Total call duration, in seconds
      NetworkStatisticsEntry -> Double
duration_2 :: Double
    }
  deriving (I32 -> NetworkStatisticsEntry -> ShowS
[NetworkStatisticsEntry] -> ShowS
NetworkStatisticsEntry -> String
(I32 -> NetworkStatisticsEntry -> ShowS)
-> (NetworkStatisticsEntry -> String)
-> ([NetworkStatisticsEntry] -> ShowS)
-> Show NetworkStatisticsEntry
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkStatisticsEntry] -> ShowS
$cshowList :: [NetworkStatisticsEntry] -> ShowS
show :: NetworkStatisticsEntry -> String
$cshow :: NetworkStatisticsEntry -> String
showsPrec :: I32 -> NetworkStatisticsEntry -> ShowS
$cshowsPrec :: I32 -> NetworkStatisticsEntry -> ShowS
Show, NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool
(NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool)
-> (NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool)
-> Eq NetworkStatisticsEntry
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool
$c/= :: NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool
== :: NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool
$c== :: NetworkStatisticsEntry -> NetworkStatisticsEntry -> Bool
Eq, (forall x. NetworkStatisticsEntry -> Rep NetworkStatisticsEntry x)
-> (forall x.
    Rep NetworkStatisticsEntry x -> NetworkStatisticsEntry)
-> Generic NetworkStatisticsEntry
forall x. Rep NetworkStatisticsEntry x -> NetworkStatisticsEntry
forall x. NetworkStatisticsEntry -> Rep NetworkStatisticsEntry x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetworkStatisticsEntry x -> NetworkStatisticsEntry
$cfrom :: forall x. NetworkStatisticsEntry -> Rep NetworkStatisticsEntry x
Generic)
data NetworkStatistics
  = -- | A full list of available network statistic entries 
  NetworkStatistics
    { -- | Point in time (Unix timestamp) when the app began collecting statistics 
      NetworkStatistics -> I32
since_date_1 :: I32,
      -- | Network statistics entries
      NetworkStatistics -> [NetworkStatisticsEntry]
entries_1 :: ([]) (NetworkStatisticsEntry)
    }
  deriving (I32 -> NetworkStatistics -> ShowS
[NetworkStatistics] -> ShowS
NetworkStatistics -> String
(I32 -> NetworkStatistics -> ShowS)
-> (NetworkStatistics -> String)
-> ([NetworkStatistics] -> ShowS)
-> Show NetworkStatistics
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NetworkStatistics] -> ShowS
$cshowList :: [NetworkStatistics] -> ShowS
show :: NetworkStatistics -> String
$cshow :: NetworkStatistics -> String
showsPrec :: I32 -> NetworkStatistics -> ShowS
$cshowsPrec :: I32 -> NetworkStatistics -> ShowS
Show, NetworkStatistics -> NetworkStatistics -> Bool
(NetworkStatistics -> NetworkStatistics -> Bool)
-> (NetworkStatistics -> NetworkStatistics -> Bool)
-> Eq NetworkStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NetworkStatistics -> NetworkStatistics -> Bool
$c/= :: NetworkStatistics -> NetworkStatistics -> Bool
== :: NetworkStatistics -> NetworkStatistics -> Bool
$c== :: NetworkStatistics -> NetworkStatistics -> Bool
Eq, (forall x. NetworkStatistics -> Rep NetworkStatistics x)
-> (forall x. Rep NetworkStatistics x -> NetworkStatistics)
-> Generic NetworkStatistics
forall x. Rep NetworkStatistics x -> NetworkStatistics
forall x. NetworkStatistics -> Rep NetworkStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep NetworkStatistics x -> NetworkStatistics
$cfrom :: forall x. NetworkStatistics -> Rep NetworkStatistics x
Generic)
data AutoDownloadSettings
  = -- | Contains auto-download settings
  AutoDownloadSettings
    { -- | True, if the auto-download is enabled
      AutoDownloadSettings -> Bool
is_auto_download_enabled_1 :: Bool,
      -- | The maximum size of a photo file to be auto-downloaded
      AutoDownloadSettings -> I32
max_photo_file_size_1 :: I32,
      -- | The maximum size of a video file to be auto-downloaded
      AutoDownloadSettings -> I32
max_video_file_size_1 :: I32,
      -- | The maximum size of other file types to be auto-downloaded
      AutoDownloadSettings -> I32
max_other_file_size_1 :: I32,
      -- | The maximum suggested bitrate for uploaded videos
      AutoDownloadSettings -> I32
video_upload_bitrate_1 :: I32,
      -- | True, if the beginning of videos needs to be preloaded for instant playback
      AutoDownloadSettings -> Bool
preload_large_videos_1 :: Bool,
      -- | True, if the next audio track needs to be preloaded while the user is listening to an audio file
      AutoDownloadSettings -> Bool
preload_next_audio_1 :: Bool,
      -- | True, if "use less data for calls" option needs to be enabled
      AutoDownloadSettings -> Bool
use_less_data_for_calls_1 :: Bool
    }
  deriving (I32 -> AutoDownloadSettings -> ShowS
[AutoDownloadSettings] -> ShowS
AutoDownloadSettings -> String
(I32 -> AutoDownloadSettings -> ShowS)
-> (AutoDownloadSettings -> String)
-> ([AutoDownloadSettings] -> ShowS)
-> Show AutoDownloadSettings
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoDownloadSettings] -> ShowS
$cshowList :: [AutoDownloadSettings] -> ShowS
show :: AutoDownloadSettings -> String
$cshow :: AutoDownloadSettings -> String
showsPrec :: I32 -> AutoDownloadSettings -> ShowS
$cshowsPrec :: I32 -> AutoDownloadSettings -> ShowS
Show, AutoDownloadSettings -> AutoDownloadSettings -> Bool
(AutoDownloadSettings -> AutoDownloadSettings -> Bool)
-> (AutoDownloadSettings -> AutoDownloadSettings -> Bool)
-> Eq AutoDownloadSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoDownloadSettings -> AutoDownloadSettings -> Bool
$c/= :: AutoDownloadSettings -> AutoDownloadSettings -> Bool
== :: AutoDownloadSettings -> AutoDownloadSettings -> Bool
$c== :: AutoDownloadSettings -> AutoDownloadSettings -> Bool
Eq, (forall x. AutoDownloadSettings -> Rep AutoDownloadSettings x)
-> (forall x. Rep AutoDownloadSettings x -> AutoDownloadSettings)
-> Generic AutoDownloadSettings
forall x. Rep AutoDownloadSettings x -> AutoDownloadSettings
forall x. AutoDownloadSettings -> Rep AutoDownloadSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AutoDownloadSettings x -> AutoDownloadSettings
$cfrom :: forall x. AutoDownloadSettings -> Rep AutoDownloadSettings x
Generic)
data AutoDownloadSettingsPresets
  = -- | Contains auto-download settings presets for the user
  AutoDownloadSettingsPresets
    { -- | Preset with lowest settings; supposed to be used by default when roaming
      AutoDownloadSettingsPresets -> AutoDownloadSettings
low_1 :: AutoDownloadSettings,
      -- | Preset with medium settings; supposed to be used by default when using mobile data
      AutoDownloadSettingsPresets -> AutoDownloadSettings
medium_1 :: AutoDownloadSettings,
      -- | Preset with highest settings; supposed to be used by default when connected on Wi-Fi
      AutoDownloadSettingsPresets -> AutoDownloadSettings
high_1 :: AutoDownloadSettings
    }
  deriving (I32 -> AutoDownloadSettingsPresets -> ShowS
[AutoDownloadSettingsPresets] -> ShowS
AutoDownloadSettingsPresets -> String
(I32 -> AutoDownloadSettingsPresets -> ShowS)
-> (AutoDownloadSettingsPresets -> String)
-> ([AutoDownloadSettingsPresets] -> ShowS)
-> Show AutoDownloadSettingsPresets
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AutoDownloadSettingsPresets] -> ShowS
$cshowList :: [AutoDownloadSettingsPresets] -> ShowS
show :: AutoDownloadSettingsPresets -> String
$cshow :: AutoDownloadSettingsPresets -> String
showsPrec :: I32 -> AutoDownloadSettingsPresets -> ShowS
$cshowsPrec :: I32 -> AutoDownloadSettingsPresets -> ShowS
Show, AutoDownloadSettingsPresets -> AutoDownloadSettingsPresets -> Bool
(AutoDownloadSettingsPresets
 -> AutoDownloadSettingsPresets -> Bool)
-> (AutoDownloadSettingsPresets
    -> AutoDownloadSettingsPresets -> Bool)
-> Eq AutoDownloadSettingsPresets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AutoDownloadSettingsPresets -> AutoDownloadSettingsPresets -> Bool
$c/= :: AutoDownloadSettingsPresets -> AutoDownloadSettingsPresets -> Bool
== :: AutoDownloadSettingsPresets -> AutoDownloadSettingsPresets -> Bool
$c== :: AutoDownloadSettingsPresets -> AutoDownloadSettingsPresets -> Bool
Eq, (forall x.
 AutoDownloadSettingsPresets -> Rep AutoDownloadSettingsPresets x)
-> (forall x.
    Rep AutoDownloadSettingsPresets x -> AutoDownloadSettingsPresets)
-> Generic AutoDownloadSettingsPresets
forall x.
Rep AutoDownloadSettingsPresets x -> AutoDownloadSettingsPresets
forall x.
AutoDownloadSettingsPresets -> Rep AutoDownloadSettingsPresets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AutoDownloadSettingsPresets x -> AutoDownloadSettingsPresets
$cfrom :: forall x.
AutoDownloadSettingsPresets -> Rep AutoDownloadSettingsPresets x
Generic)
-- | Describes the current state of the connection to Telegram servers
data ConnectionState
  = -- | Currently waiting for the network to become available. Use setNetworkType to change the available network type
  ConnectionStateWaitingForNetwork
    { 
    }
  | -- | Currently establishing a connection with a proxy server
  ConnectionStateConnectingToProxy
    { 
    }
  | -- | Currently establishing a connection to the Telegram servers
  ConnectionStateConnecting
    { 
    }
  | -- | Downloading data received while the client was offline
  ConnectionStateUpdating
    { 
    }
  | -- | There is a working connection to the Telegram servers
  ConnectionStateReady
    { 
    }
  deriving (I32 -> ConnectionState -> ShowS
[ConnectionState] -> ShowS
ConnectionState -> String
(I32 -> ConnectionState -> ShowS)
-> (ConnectionState -> String)
-> ([ConnectionState] -> ShowS)
-> Show ConnectionState
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConnectionState] -> ShowS
$cshowList :: [ConnectionState] -> ShowS
show :: ConnectionState -> String
$cshow :: ConnectionState -> String
showsPrec :: I32 -> ConnectionState -> ShowS
$cshowsPrec :: I32 -> ConnectionState -> ShowS
Show, ConnectionState -> ConnectionState -> Bool
(ConnectionState -> ConnectionState -> Bool)
-> (ConnectionState -> ConnectionState -> Bool)
-> Eq ConnectionState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConnectionState -> ConnectionState -> Bool
$c/= :: ConnectionState -> ConnectionState -> Bool
== :: ConnectionState -> ConnectionState -> Bool
$c== :: ConnectionState -> ConnectionState -> Bool
Eq, (forall x. ConnectionState -> Rep ConnectionState x)
-> (forall x. Rep ConnectionState x -> ConnectionState)
-> Generic ConnectionState
forall x. Rep ConnectionState x -> ConnectionState
forall x. ConnectionState -> Rep ConnectionState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConnectionState x -> ConnectionState
$cfrom :: forall x. ConnectionState -> Rep ConnectionState x
Generic)
-- | Represents the categories of chats for which a list of frequently used chats can be retrieved
data TopChatCategory
  = -- | A category containing frequently used private chats with non-bot users
  TopChatCategoryUsers
    { 
    }
  | -- | A category containing frequently used private chats with bot users
  TopChatCategoryBots
    { 
    }
  | -- | A category containing frequently used basic groups and supergroups
  TopChatCategoryGroups
    { 
    }
  | -- | A category containing frequently used channels
  TopChatCategoryChannels
    { 
    }
  | -- | A category containing frequently used chats with inline bots sorted by their usage in inline mode
  TopChatCategoryInlineBots
    { 
    }
  | -- | A category containing frequently used chats used for calls
  TopChatCategoryCalls
    { 
    }
  | -- | A category containing frequently used chats used to forward messages
  TopChatCategoryForwardChats
    { 
    }
  deriving (I32 -> TopChatCategory -> ShowS
[TopChatCategory] -> ShowS
TopChatCategory -> String
(I32 -> TopChatCategory -> ShowS)
-> (TopChatCategory -> String)
-> ([TopChatCategory] -> ShowS)
-> Show TopChatCategory
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TopChatCategory] -> ShowS
$cshowList :: [TopChatCategory] -> ShowS
show :: TopChatCategory -> String
$cshow :: TopChatCategory -> String
showsPrec :: I32 -> TopChatCategory -> ShowS
$cshowsPrec :: I32 -> TopChatCategory -> ShowS
Show, TopChatCategory -> TopChatCategory -> Bool
(TopChatCategory -> TopChatCategory -> Bool)
-> (TopChatCategory -> TopChatCategory -> Bool)
-> Eq TopChatCategory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TopChatCategory -> TopChatCategory -> Bool
$c/= :: TopChatCategory -> TopChatCategory -> Bool
== :: TopChatCategory -> TopChatCategory -> Bool
$c== :: TopChatCategory -> TopChatCategory -> Bool
Eq, (forall x. TopChatCategory -> Rep TopChatCategory x)
-> (forall x. Rep TopChatCategory x -> TopChatCategory)
-> Generic TopChatCategory
forall x. Rep TopChatCategory x -> TopChatCategory
forall x. TopChatCategory -> Rep TopChatCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TopChatCategory x -> TopChatCategory
$cfrom :: forall x. TopChatCategory -> Rep TopChatCategory x
Generic)
-- | Describes the type of a URL linking to an internal Telegram entity
data TMeUrlType
  = -- | A URL linking to a user 
  TMeUrlTypeUser
    { -- | Identifier of the user
      TMeUrlType -> I32
user_id_1 :: I32
    }
  | -- | A URL linking to a public supergroup or channel 
  TMeUrlTypeSupergroup
    { -- | Identifier of the supergroup or channel
      TMeUrlType -> I32
supergroup_id_2 :: I53
    }
  | -- | A chat invite link 
  TMeUrlTypeChatInvite
    { -- | Chat invite link info
      TMeUrlType -> ChatInviteLinkInfo
info_3 :: ChatInviteLinkInfo
    }
  | -- | A URL linking to a sticker set 
  TMeUrlTypeStickerSet
    { -- | Identifier of the sticker set
      TMeUrlType -> I64
sticker_set_id_4 :: I64
    }
  deriving (I32 -> TMeUrlType -> ShowS
[TMeUrlType] -> ShowS
TMeUrlType -> String
(I32 -> TMeUrlType -> ShowS)
-> (TMeUrlType -> String)
-> ([TMeUrlType] -> ShowS)
-> Show TMeUrlType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TMeUrlType] -> ShowS
$cshowList :: [TMeUrlType] -> ShowS
show :: TMeUrlType -> String
$cshow :: TMeUrlType -> String
showsPrec :: I32 -> TMeUrlType -> ShowS
$cshowsPrec :: I32 -> TMeUrlType -> ShowS
Show, TMeUrlType -> TMeUrlType -> Bool
(TMeUrlType -> TMeUrlType -> Bool)
-> (TMeUrlType -> TMeUrlType -> Bool) -> Eq TMeUrlType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TMeUrlType -> TMeUrlType -> Bool
$c/= :: TMeUrlType -> TMeUrlType -> Bool
== :: TMeUrlType -> TMeUrlType -> Bool
$c== :: TMeUrlType -> TMeUrlType -> Bool
Eq, (forall x. TMeUrlType -> Rep TMeUrlType x)
-> (forall x. Rep TMeUrlType x -> TMeUrlType) -> Generic TMeUrlType
forall x. Rep TMeUrlType x -> TMeUrlType
forall x. TMeUrlType -> Rep TMeUrlType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TMeUrlType x -> TMeUrlType
$cfrom :: forall x. TMeUrlType -> Rep TMeUrlType x
Generic)
data TMeUrl
  = -- | Represents a URL linking to an internal Telegram entity 
  TMeUrl
    { -- | URL 
      TMeUrl -> T
url_1 :: T,
      -- | Type of the URL
      TMeUrl -> TMeUrlType
type_1 :: TMeUrlType
    }
  deriving (I32 -> TMeUrl -> ShowS
[TMeUrl] -> ShowS
TMeUrl -> String
(I32 -> TMeUrl -> ShowS)
-> (TMeUrl -> String) -> ([TMeUrl] -> ShowS) -> Show TMeUrl
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TMeUrl] -> ShowS
$cshowList :: [TMeUrl] -> ShowS
show :: TMeUrl -> String
$cshow :: TMeUrl -> String
showsPrec :: I32 -> TMeUrl -> ShowS
$cshowsPrec :: I32 -> TMeUrl -> ShowS
Show, TMeUrl -> TMeUrl -> Bool
(TMeUrl -> TMeUrl -> Bool)
-> (TMeUrl -> TMeUrl -> Bool) -> Eq TMeUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TMeUrl -> TMeUrl -> Bool
$c/= :: TMeUrl -> TMeUrl -> Bool
== :: TMeUrl -> TMeUrl -> Bool
$c== :: TMeUrl -> TMeUrl -> Bool
Eq, (forall x. TMeUrl -> Rep TMeUrl x)
-> (forall x. Rep TMeUrl x -> TMeUrl) -> Generic TMeUrl
forall x. Rep TMeUrl x -> TMeUrl
forall x. TMeUrl -> Rep TMeUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TMeUrl x -> TMeUrl
$cfrom :: forall x. TMeUrl -> Rep TMeUrl x
Generic)
data TMeUrls
  = -- | Contains a list of t.me URLs 
  TMeUrls
    { -- | List of URLs
      TMeUrls -> [TMeUrl]
urls_1 :: ([]) (TMeUrl)
    }
  deriving (I32 -> TMeUrls -> ShowS
[TMeUrls] -> ShowS
TMeUrls -> String
(I32 -> TMeUrls -> ShowS)
-> (TMeUrls -> String) -> ([TMeUrls] -> ShowS) -> Show TMeUrls
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TMeUrls] -> ShowS
$cshowList :: [TMeUrls] -> ShowS
show :: TMeUrls -> String
$cshow :: TMeUrls -> String
showsPrec :: I32 -> TMeUrls -> ShowS
$cshowsPrec :: I32 -> TMeUrls -> ShowS
Show, TMeUrls -> TMeUrls -> Bool
(TMeUrls -> TMeUrls -> Bool)
-> (TMeUrls -> TMeUrls -> Bool) -> Eq TMeUrls
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TMeUrls -> TMeUrls -> Bool
$c/= :: TMeUrls -> TMeUrls -> Bool
== :: TMeUrls -> TMeUrls -> Bool
$c== :: TMeUrls -> TMeUrls -> Bool
Eq, (forall x. TMeUrls -> Rep TMeUrls x)
-> (forall x. Rep TMeUrls x -> TMeUrls) -> Generic TMeUrls
forall x. Rep TMeUrls x -> TMeUrls
forall x. TMeUrls -> Rep TMeUrls x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TMeUrls x -> TMeUrls
$cfrom :: forall x. TMeUrls -> Rep TMeUrls x
Generic)
data Count
  = -- | Contains a counter 
  Count
    { -- | Count
      Count -> I32
count_1 :: I32
    }
  deriving (I32 -> Count -> ShowS
[Count] -> ShowS
Count -> String
(I32 -> Count -> ShowS)
-> (Count -> String) -> ([Count] -> ShowS) -> Show Count
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Count] -> ShowS
$cshowList :: [Count] -> ShowS
show :: Count -> String
$cshow :: Count -> String
showsPrec :: I32 -> Count -> ShowS
$cshowsPrec :: I32 -> Count -> ShowS
Show, Count -> Count -> Bool
(Count -> Count -> Bool) -> (Count -> Count -> Bool) -> Eq Count
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Count -> Count -> Bool
$c/= :: Count -> Count -> Bool
== :: Count -> Count -> Bool
$c== :: Count -> Count -> Bool
Eq, (forall x. Count -> Rep Count x)
-> (forall x. Rep Count x -> Count) -> Generic Count
forall x. Rep Count x -> Count
forall x. Count -> Rep Count x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Count x -> Count
$cfrom :: forall x. Count -> Rep Count x
Generic)
data Text
  = -- | Contains some text 
  Text
    { -- | Text
      Text -> T
text_1 :: T
    }
  deriving (I32 -> Text -> ShowS
[Text] -> ShowS
Text -> String
(I32 -> Text -> ShowS)
-> (Text -> String) -> ([Text] -> ShowS) -> Show Text
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Text] -> ShowS
$cshowList :: [Text] -> ShowS
show :: Text -> String
$cshow :: Text -> String
showsPrec :: I32 -> Text -> ShowS
$cshowsPrec :: I32 -> Text -> ShowS
Show, Text -> Text -> Bool
(Text -> Text -> Bool) -> (Text -> Text -> Bool) -> Eq Text
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Text -> Text -> Bool
$c/= :: Text -> Text -> Bool
== :: Text -> Text -> Bool
$c== :: Text -> Text -> Bool
Eq, (forall x. Text -> Rep Text x)
-> (forall x. Rep Text x -> Text) -> Generic Text
forall x. Rep Text x -> Text
forall x. Text -> Rep Text x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Text x -> Text
$cfrom :: forall x. Text -> Rep Text x
Generic)
data Seconds
  = -- | Contains a value representing a number of seconds 
  Seconds
    { -- | Number of seconds
      Seconds -> Double
seconds_1 :: Double
    }
  deriving (I32 -> Seconds -> ShowS
[Seconds] -> ShowS
Seconds -> String
(I32 -> Seconds -> ShowS)
-> (Seconds -> String) -> ([Seconds] -> ShowS) -> Show Seconds
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Seconds] -> ShowS
$cshowList :: [Seconds] -> ShowS
show :: Seconds -> String
$cshow :: Seconds -> String
showsPrec :: I32 -> Seconds -> ShowS
$cshowsPrec :: I32 -> Seconds -> ShowS
Show, 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, (forall x. Seconds -> Rep Seconds x)
-> (forall x. Rep Seconds x -> Seconds) -> Generic Seconds
forall x. Rep Seconds x -> Seconds
forall x. Seconds -> Rep Seconds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Seconds x -> Seconds
$cfrom :: forall x. Seconds -> Rep Seconds x
Generic)
data DeepLinkInfo
  = -- | Contains information about a tg:// deep link 
  DeepLinkInfo
    { -- | Text to be shown to the user 
      DeepLinkInfo -> FormattedText
text_1 :: FormattedText,
      -- | True, if user should be asked to update the application
      DeepLinkInfo -> Bool
need_update_application_1 :: Bool
    }
  deriving (I32 -> DeepLinkInfo -> ShowS
[DeepLinkInfo] -> ShowS
DeepLinkInfo -> String
(I32 -> DeepLinkInfo -> ShowS)
-> (DeepLinkInfo -> String)
-> ([DeepLinkInfo] -> ShowS)
-> Show DeepLinkInfo
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeepLinkInfo] -> ShowS
$cshowList :: [DeepLinkInfo] -> ShowS
show :: DeepLinkInfo -> String
$cshow :: DeepLinkInfo -> String
showsPrec :: I32 -> DeepLinkInfo -> ShowS
$cshowsPrec :: I32 -> DeepLinkInfo -> ShowS
Show, DeepLinkInfo -> DeepLinkInfo -> Bool
(DeepLinkInfo -> DeepLinkInfo -> Bool)
-> (DeepLinkInfo -> DeepLinkInfo -> Bool) -> Eq DeepLinkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeepLinkInfo -> DeepLinkInfo -> Bool
$c/= :: DeepLinkInfo -> DeepLinkInfo -> Bool
== :: DeepLinkInfo -> DeepLinkInfo -> Bool
$c== :: DeepLinkInfo -> DeepLinkInfo -> Bool
Eq, (forall x. DeepLinkInfo -> Rep DeepLinkInfo x)
-> (forall x. Rep DeepLinkInfo x -> DeepLinkInfo)
-> Generic DeepLinkInfo
forall x. Rep DeepLinkInfo x -> DeepLinkInfo
forall x. DeepLinkInfo -> Rep DeepLinkInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeepLinkInfo x -> DeepLinkInfo
$cfrom :: forall x. DeepLinkInfo -> Rep DeepLinkInfo x
Generic)
-- | Describes the way the text should be parsed for TextEntities
data TextParseMode
  = -- | The text uses Markdown-style formatting
  TextParseModeMarkdown
    { -- | Version of the parser: 0 or 1 - Telegram Bot API "Markdown" parse mode, 2 - Telegram Bot API "MarkdownV2" parse mode
      TextParseMode -> I32
version_1 :: I32
    }
  | -- | The text uses HTML-style formatting. The same as Telegram Bot API "HTML" parse mode
  TextParseModeHTML
    { 
    }
  deriving (I32 -> TextParseMode -> ShowS
[TextParseMode] -> ShowS
TextParseMode -> String
(I32 -> TextParseMode -> ShowS)
-> (TextParseMode -> String)
-> ([TextParseMode] -> ShowS)
-> Show TextParseMode
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextParseMode] -> ShowS
$cshowList :: [TextParseMode] -> ShowS
show :: TextParseMode -> String
$cshow :: TextParseMode -> String
showsPrec :: I32 -> TextParseMode -> ShowS
$cshowsPrec :: I32 -> TextParseMode -> ShowS
Show, TextParseMode -> TextParseMode -> Bool
(TextParseMode -> TextParseMode -> Bool)
-> (TextParseMode -> TextParseMode -> Bool) -> Eq TextParseMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextParseMode -> TextParseMode -> Bool
$c/= :: TextParseMode -> TextParseMode -> Bool
== :: TextParseMode -> TextParseMode -> Bool
$c== :: TextParseMode -> TextParseMode -> Bool
Eq, (forall x. TextParseMode -> Rep TextParseMode x)
-> (forall x. Rep TextParseMode x -> TextParseMode)
-> Generic TextParseMode
forall x. Rep TextParseMode x -> TextParseMode
forall x. TextParseMode -> Rep TextParseMode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TextParseMode x -> TextParseMode
$cfrom :: forall x. TextParseMode -> Rep TextParseMode x
Generic)
-- | Describes the type of a proxy server
data ProxyType
  = -- | A SOCKS5 proxy server 
  ProxyTypeSocks5
    { -- | Username for logging in; may be empty 
      ProxyType -> T
username_1 :: T,
      -- | Password for logging in; may be empty
      ProxyType -> T
password_1 :: T
    }
  | -- | A HTTP transparent proxy server 
  ProxyTypeHttp
    { -- | Username for logging in; may be empty 
      ProxyType -> T
username_2 :: T,
      -- | Password for logging in; may be empty 
      ProxyType -> T
password_2 :: T,
      -- | Pass true if the proxy supports only HTTP requests and doesn't support transparent TCP connections via HTTP CONNECT method
      ProxyType -> Bool
http_only_2 :: Bool
    }
  | -- | An MTProto proxy server 
  ProxyTypeMtproto
    { -- | The proxy's secret in hexadecimal encoding
      ProxyType -> T
secret_3 :: T
    }
  deriving (I32 -> ProxyType -> ShowS
[ProxyType] -> ShowS
ProxyType -> String
(I32 -> ProxyType -> ShowS)
-> (ProxyType -> String)
-> ([ProxyType] -> ShowS)
-> Show ProxyType
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProxyType] -> ShowS
$cshowList :: [ProxyType] -> ShowS
show :: ProxyType -> String
$cshow :: ProxyType -> String
showsPrec :: I32 -> ProxyType -> ShowS
$cshowsPrec :: I32 -> ProxyType -> ShowS
Show, ProxyType -> ProxyType -> Bool
(ProxyType -> ProxyType -> Bool)
-> (ProxyType -> ProxyType -> Bool) -> Eq ProxyType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProxyType -> ProxyType -> Bool
$c/= :: ProxyType -> ProxyType -> Bool
== :: ProxyType -> ProxyType -> Bool
$c== :: ProxyType -> ProxyType -> Bool
Eq, (forall x. ProxyType -> Rep ProxyType x)
-> (forall x. Rep ProxyType x -> ProxyType) -> Generic ProxyType
forall x. Rep ProxyType x -> ProxyType
forall x. ProxyType -> Rep ProxyType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProxyType x -> ProxyType
$cfrom :: forall x. ProxyType -> Rep ProxyType x
Generic)
data Proxy
  = -- | Contains information about a proxy server 
  Proxy
    { -- | Unique identifier of the proxy 
      Proxy -> I32
id_1 :: I32,
      -- | Proxy server IP address 
      Proxy -> T
server_1 :: T,
      -- | Proxy server port 
      Proxy -> I32
port_1 :: I32,
      -- | Point in time (Unix timestamp) when the proxy was last used; 0 if never 
      Proxy -> I32
last_used_date_1 :: I32,
      -- | True, if the proxy is enabled now 
      Proxy -> Bool
is_enabled_1 :: Bool,
      -- | Type of the proxy
      Proxy -> ProxyType
type_1 :: ProxyType
    }
  deriving (I32 -> Proxy -> ShowS
[Proxy] -> ShowS
Proxy -> String
(I32 -> Proxy -> ShowS)
-> (Proxy -> String) -> ([Proxy] -> ShowS) -> Show Proxy
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Proxy] -> ShowS
$cshowList :: [Proxy] -> ShowS
show :: Proxy -> String
$cshow :: Proxy -> String
showsPrec :: I32 -> Proxy -> ShowS
$cshowsPrec :: I32 -> Proxy -> ShowS
Show, Proxy -> Proxy -> Bool
(Proxy -> Proxy -> Bool) -> (Proxy -> Proxy -> Bool) -> Eq Proxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Proxy -> Proxy -> Bool
$c/= :: Proxy -> Proxy -> Bool
== :: Proxy -> Proxy -> Bool
$c== :: Proxy -> Proxy -> Bool
Eq, (forall x. Proxy -> Rep Proxy x)
-> (forall x. Rep Proxy x -> Proxy) -> Generic Proxy
forall x. Rep Proxy x -> Proxy
forall x. Proxy -> Rep Proxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Proxy x -> Proxy
$cfrom :: forall x. Proxy -> Rep Proxy x
Generic)
data Proxies
  = -- | Represents a list of proxy servers 
  Proxies
    { -- | List of proxy servers
      Proxies -> [Proxy]
proxies_1 :: ([]) (Proxy)
    }
  deriving (I32 -> Proxies -> ShowS
[Proxies] -> ShowS
Proxies -> String
(I32 -> Proxies -> ShowS)
-> (Proxies -> String) -> ([Proxies] -> ShowS) -> Show Proxies
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Proxies] -> ShowS
$cshowList :: [Proxies] -> ShowS
show :: Proxies -> String
$cshow :: Proxies -> String
showsPrec :: I32 -> Proxies -> ShowS
$cshowsPrec :: I32 -> Proxies -> ShowS
Show, Proxies -> Proxies -> Bool
(Proxies -> Proxies -> Bool)
-> (Proxies -> Proxies -> Bool) -> Eq Proxies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Proxies -> Proxies -> Bool
$c/= :: Proxies -> Proxies -> Bool
== :: Proxies -> Proxies -> Bool
$c== :: Proxies -> Proxies -> Bool
Eq, (forall x. Proxies -> Rep Proxies x)
-> (forall x. Rep Proxies x -> Proxies) -> Generic Proxies
forall x. Rep Proxies x -> Proxies
forall x. Proxies -> Rep Proxies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Proxies x -> Proxies
$cfrom :: forall x. Proxies -> Rep Proxies x
Generic)
-- | Describes a sticker that needs to be added to a sticker set
data InputSticker
  = -- | A static sticker in PNG format, which will be converted to WEBP server-side
  InputStickerStatic
    { -- | PNG image with the sticker; must be up to 512 KB in size and fit in a 512x512 square
      InputSticker -> InputFile
sticker_1 :: InputFile,
      -- | Emojis corresponding to the sticker
      InputSticker -> T
emojis_1 :: T,
      -- | For masks, position where the mask should be placed; may be null
      InputSticker -> MaskPosition
mask_position_1 :: MaskPosition
    }
  | -- | An animated sticker in TGS format
  InputStickerAnimated
    { -- | File with the animated sticker. Only local or uploaded within a week files are supported. See https://core.telegram.org/animated_stickers#technical-requirements for technical requirements
      InputSticker -> InputFile
sticker_2 :: InputFile,
      -- | Emojis corresponding to the sticker
      InputSticker -> T
emojis_2 :: T
    }
  deriving (I32 -> InputSticker -> ShowS
[InputSticker] -> ShowS
InputSticker -> String
(I32 -> InputSticker -> ShowS)
-> (InputSticker -> String)
-> ([InputSticker] -> ShowS)
-> Show InputSticker
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InputSticker] -> ShowS
$cshowList :: [InputSticker] -> ShowS
show :: InputSticker -> String
$cshow :: InputSticker -> String
showsPrec :: I32 -> InputSticker -> ShowS
$cshowsPrec :: I32 -> InputSticker -> ShowS
Show, InputSticker -> InputSticker -> Bool
(InputSticker -> InputSticker -> Bool)
-> (InputSticker -> InputSticker -> Bool) -> Eq InputSticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputSticker -> InputSticker -> Bool
$c/= :: InputSticker -> InputSticker -> Bool
== :: InputSticker -> InputSticker -> Bool
$c== :: InputSticker -> InputSticker -> Bool
Eq, (forall x. InputSticker -> Rep InputSticker x)
-> (forall x. Rep InputSticker x -> InputSticker)
-> Generic InputSticker
forall x. Rep InputSticker x -> InputSticker
forall x. InputSticker -> Rep InputSticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InputSticker x -> InputSticker
$cfrom :: forall x. InputSticker -> Rep InputSticker x
Generic)
data DateRange
  = -- | Represents a date range 
  DateRange
    { -- | Point in time (Unix timestamp) at which the date range begins 
      DateRange -> I32
start_date_1 :: I32,
      -- | Point in time (Unix timestamp) at which the date range ends
      DateRange -> I32
end_date_1 :: I32
    }
  deriving (I32 -> DateRange -> ShowS
[DateRange] -> ShowS
DateRange -> String
(I32 -> DateRange -> ShowS)
-> (DateRange -> String)
-> ([DateRange] -> ShowS)
-> Show DateRange
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateRange] -> ShowS
$cshowList :: [DateRange] -> ShowS
show :: DateRange -> String
$cshow :: DateRange -> String
showsPrec :: I32 -> DateRange -> ShowS
$cshowsPrec :: I32 -> DateRange -> ShowS
Show, DateRange -> DateRange -> Bool
(DateRange -> DateRange -> Bool)
-> (DateRange -> DateRange -> Bool) -> Eq DateRange
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateRange -> DateRange -> Bool
$c/= :: DateRange -> DateRange -> Bool
== :: DateRange -> DateRange -> Bool
$c== :: DateRange -> DateRange -> Bool
Eq, (forall x. DateRange -> Rep DateRange x)
-> (forall x. Rep DateRange x -> DateRange) -> Generic DateRange
forall x. Rep DateRange x -> DateRange
forall x. DateRange -> Rep DateRange x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DateRange x -> DateRange
$cfrom :: forall x. DateRange -> Rep DateRange x
Generic)
data StatisticsValue
  = -- | A statistics value 
  StatisticsValue
    { -- | The value 
      StatisticsValue -> Double
value_1 :: Double,
      -- | The value for the previous day 
      StatisticsValue -> Double
previous_value_1 :: Double,
      -- | The growth rate of the value, as a percentage
      StatisticsValue -> Double
growth_rate_percentage_1 :: Double
    }
  deriving (I32 -> StatisticsValue -> ShowS
[StatisticsValue] -> ShowS
StatisticsValue -> String
(I32 -> StatisticsValue -> ShowS)
-> (StatisticsValue -> String)
-> ([StatisticsValue] -> ShowS)
-> Show StatisticsValue
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatisticsValue] -> ShowS
$cshowList :: [StatisticsValue] -> ShowS
show :: StatisticsValue -> String
$cshow :: StatisticsValue -> String
showsPrec :: I32 -> StatisticsValue -> ShowS
$cshowsPrec :: I32 -> StatisticsValue -> ShowS
Show, StatisticsValue -> StatisticsValue -> Bool
(StatisticsValue -> StatisticsValue -> Bool)
-> (StatisticsValue -> StatisticsValue -> Bool)
-> Eq StatisticsValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatisticsValue -> StatisticsValue -> Bool
$c/= :: StatisticsValue -> StatisticsValue -> Bool
== :: StatisticsValue -> StatisticsValue -> Bool
$c== :: StatisticsValue -> StatisticsValue -> Bool
Eq, (forall x. StatisticsValue -> Rep StatisticsValue x)
-> (forall x. Rep StatisticsValue x -> StatisticsValue)
-> Generic StatisticsValue
forall x. Rep StatisticsValue x -> StatisticsValue
forall x. StatisticsValue -> Rep StatisticsValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StatisticsValue x -> StatisticsValue
$cfrom :: forall x. StatisticsValue -> Rep StatisticsValue x
Generic)
-- | Describes a statistics graph
data StatisticsGraph
  = -- | A graph data 
  StatisticsGraphData
    { -- | Graph data in JSON format 
      StatisticsGraph -> T
json_data_1 :: T,
      -- | If non-empty, a token which can be used to receive a zoomed in graph
      StatisticsGraph -> T
zoom_token_1 :: T
    }
  | -- | The graph data to be asynchronously loaded through getChatStatisticsGraph 
  StatisticsGraphAsync
    { -- | The token to use for data loading
      StatisticsGraph -> T
token_2 :: T
    }
  | -- | An error message to be shown to the user instead of the graph 
  StatisticsGraphError
    { -- | The error message
      StatisticsGraph -> T
error_message_3 :: T
    }
  deriving (I32 -> StatisticsGraph -> ShowS
[StatisticsGraph] -> ShowS
StatisticsGraph -> String
(I32 -> StatisticsGraph -> ShowS)
-> (StatisticsGraph -> String)
-> ([StatisticsGraph] -> ShowS)
-> Show StatisticsGraph
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StatisticsGraph] -> ShowS
$cshowList :: [StatisticsGraph] -> ShowS
show :: StatisticsGraph -> String
$cshow :: StatisticsGraph -> String
showsPrec :: I32 -> StatisticsGraph -> ShowS
$cshowsPrec :: I32 -> StatisticsGraph -> ShowS
Show, StatisticsGraph -> StatisticsGraph -> Bool
(StatisticsGraph -> StatisticsGraph -> Bool)
-> (StatisticsGraph -> StatisticsGraph -> Bool)
-> Eq StatisticsGraph
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StatisticsGraph -> StatisticsGraph -> Bool
$c/= :: StatisticsGraph -> StatisticsGraph -> Bool
== :: StatisticsGraph -> StatisticsGraph -> Bool
$c== :: StatisticsGraph -> StatisticsGraph -> Bool
Eq, (forall x. StatisticsGraph -> Rep StatisticsGraph x)
-> (forall x. Rep StatisticsGraph x -> StatisticsGraph)
-> Generic StatisticsGraph
forall x. Rep StatisticsGraph x -> StatisticsGraph
forall x. StatisticsGraph -> Rep StatisticsGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StatisticsGraph x -> StatisticsGraph
$cfrom :: forall x. StatisticsGraph -> Rep StatisticsGraph x
Generic)
data ChatStatisticsMessageInteractionCounters
  = -- | Contains statistics about interactions with a message
  ChatStatisticsMessageInteractionCounters
    { -- | Message identifier
      ChatStatisticsMessageInteractionCounters -> I32
message_id_1 :: I53,
      -- | Number of times the message was viewed
      ChatStatisticsMessageInteractionCounters -> I32
view_count_1 :: I32,
      -- | Number of times the message was forwarded
      ChatStatisticsMessageInteractionCounters -> I32
forward_count_1 :: I32
    }
  deriving (I32 -> ChatStatisticsMessageInteractionCounters -> ShowS
[ChatStatisticsMessageInteractionCounters] -> ShowS
ChatStatisticsMessageInteractionCounters -> String
(I32 -> ChatStatisticsMessageInteractionCounters -> ShowS)
-> (ChatStatisticsMessageInteractionCounters -> String)
-> ([ChatStatisticsMessageInteractionCounters] -> ShowS)
-> Show ChatStatisticsMessageInteractionCounters
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatStatisticsMessageInteractionCounters] -> ShowS
$cshowList :: [ChatStatisticsMessageInteractionCounters] -> ShowS
show :: ChatStatisticsMessageInteractionCounters -> String
$cshow :: ChatStatisticsMessageInteractionCounters -> String
showsPrec :: I32 -> ChatStatisticsMessageInteractionCounters -> ShowS
$cshowsPrec :: I32 -> ChatStatisticsMessageInteractionCounters -> ShowS
Show, ChatStatisticsMessageInteractionCounters
-> ChatStatisticsMessageInteractionCounters -> Bool
(ChatStatisticsMessageInteractionCounters
 -> ChatStatisticsMessageInteractionCounters -> Bool)
-> (ChatStatisticsMessageInteractionCounters
    -> ChatStatisticsMessageInteractionCounters -> Bool)
-> Eq ChatStatisticsMessageInteractionCounters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatStatisticsMessageInteractionCounters
-> ChatStatisticsMessageInteractionCounters -> Bool
$c/= :: ChatStatisticsMessageInteractionCounters
-> ChatStatisticsMessageInteractionCounters -> Bool
== :: ChatStatisticsMessageInteractionCounters
-> ChatStatisticsMessageInteractionCounters -> Bool
$c== :: ChatStatisticsMessageInteractionCounters
-> ChatStatisticsMessageInteractionCounters -> Bool
Eq, (forall x.
 ChatStatisticsMessageInteractionCounters
 -> Rep ChatStatisticsMessageInteractionCounters x)
-> (forall x.
    Rep ChatStatisticsMessageInteractionCounters x
    -> ChatStatisticsMessageInteractionCounters)
-> Generic ChatStatisticsMessageInteractionCounters
forall x.
Rep ChatStatisticsMessageInteractionCounters x
-> ChatStatisticsMessageInteractionCounters
forall x.
ChatStatisticsMessageInteractionCounters
-> Rep ChatStatisticsMessageInteractionCounters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ChatStatisticsMessageInteractionCounters x
-> ChatStatisticsMessageInteractionCounters
$cfrom :: forall x.
ChatStatisticsMessageInteractionCounters
-> Rep ChatStatisticsMessageInteractionCounters x
Generic)
data ChatStatistics
  = -- | A detailed statistics about a chat
  ChatStatistics
    { -- | A period to which the statistics applies
      ChatStatistics -> DateRange
period_1 :: DateRange,
      -- | Number of members in the chat
      ChatStatistics -> StatisticsValue
member_count_1 :: StatisticsValue,
      -- | Mean number of times the recently sent messages was viewed
      ChatStatistics -> StatisticsValue
mean_view_count_1 :: StatisticsValue,
      -- | Mean number of times the recently sent messages was shared
      ChatStatistics -> StatisticsValue
mean_share_count_1 :: StatisticsValue,
      -- | A percentage of users with enabled notifications for the chat
      ChatStatistics -> Double
enabled_notifications_percentage_1 :: Double,
      -- | A graph containing number of members in the chat
      ChatStatistics -> StatisticsGraph
member_count_graph_1 :: StatisticsGraph,
      -- | A graph containing number of members joined and left the chat
      ChatStatistics -> StatisticsGraph
join_graph_1 :: StatisticsGraph,
      -- | A graph containing number of members muted and unmuted the chat
      ChatStatistics -> StatisticsGraph
mute_graph_1 :: StatisticsGraph,
      -- | A graph containing number of message views in a given hour in the last two weeks
      ChatStatistics -> StatisticsGraph
view_count_by_hour_graph_1 :: StatisticsGraph,
      -- | A graph containing number of message views per source
      ChatStatistics -> StatisticsGraph
view_count_by_source_graph_1 :: StatisticsGraph,
      -- | A graph containing number of new member joins per source
      ChatStatistics -> StatisticsGraph
join_by_source_graph_1 :: StatisticsGraph,
      -- | A graph containing number of users viewed chat messages per language
      ChatStatistics -> StatisticsGraph
language_graph_1 :: StatisticsGraph,
      -- | A graph containing number of chat message views and shares
      ChatStatistics -> StatisticsGraph
message_interaction_graph_1 :: StatisticsGraph,
      -- | A graph containing number of views of associated with the chat instant views
      ChatStatistics -> StatisticsGraph
instant_view_interaction_graph_1 :: StatisticsGraph,
      -- | Detailed statistics about number of views and shares of recently sent messages
      ChatStatistics -> [ChatStatisticsMessageInteractionCounters]
recent_message_interactions_1 :: ([]) (ChatStatisticsMessageInteractionCounters)
    }
  deriving (I32 -> ChatStatistics -> ShowS
[ChatStatistics] -> ShowS
ChatStatistics -> String
(I32 -> ChatStatistics -> ShowS)
-> (ChatStatistics -> String)
-> ([ChatStatistics] -> ShowS)
-> Show ChatStatistics
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChatStatistics] -> ShowS
$cshowList :: [ChatStatistics] -> ShowS
show :: ChatStatistics -> String
$cshow :: ChatStatistics -> String
showsPrec :: I32 -> ChatStatistics -> ShowS
$cshowsPrec :: I32 -> ChatStatistics -> ShowS
Show, ChatStatistics -> ChatStatistics -> Bool
(ChatStatistics -> ChatStatistics -> Bool)
-> (ChatStatistics -> ChatStatistics -> Bool) -> Eq ChatStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChatStatistics -> ChatStatistics -> Bool
$c/= :: ChatStatistics -> ChatStatistics -> Bool
== :: ChatStatistics -> ChatStatistics -> Bool
$c== :: ChatStatistics -> ChatStatistics -> Bool
Eq, (forall x. ChatStatistics -> Rep ChatStatistics x)
-> (forall x. Rep ChatStatistics x -> ChatStatistics)
-> Generic ChatStatistics
forall x. Rep ChatStatistics x -> ChatStatistics
forall x. ChatStatistics -> Rep ChatStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChatStatistics x -> ChatStatistics
$cfrom :: forall x. ChatStatistics -> Rep ChatStatistics x
Generic)
-- | Contains notifications about data changes
data Update
  = -- | The user authorization state has changed 
  UpdateAuthorizationState
    { -- | New authorization state
      Update -> AuthorizationState
authorization_state_1 :: AuthorizationState
    }
  | -- | A new message was received; can also be an outgoing message 
  UpdateNewMessage
    { -- | The new message
      Update -> Message
message_2 :: Message
    }
  | -- | A request to send a message has reached the Telegram server. This doesn't mean that the message will be sent successfully or even that the send message request will be processed. This update will be sent only if the option "use_quick_ack" is set to true. This update may be sent multiple times for the same message
  UpdateMessageSendAcknowledged
    { -- | The chat identifier of the sent message 
      Update -> I32
chat_id_3 :: I53,
      -- | A temporary message identifier
      Update -> I32
message_id_3 :: I53
    }
  | -- | A message has been successfully sent 
  UpdateMessageSendSucceeded
    { -- | Information about the sent message. Usually only the message identifier, date, and content are changed, but almost all other fields can also change 
      Update -> Message
message_4 :: Message,
      -- | The previous temporary message identifier
      Update -> I32
old_message_id_4 :: I53
    }
  | -- | A message failed to send. Be aware that some messages being sent can be irrecoverably deleted, in which case updateDeleteMessages will be received instead of this update
  UpdateMessageSendFailed
    { -- | Contains information about the message which failed to send 
      Update -> Message
message_5 :: Message,
      -- | The previous temporary message identifier 
      Update -> I32
old_message_id_5 :: I53,
      -- | An error code 
      Update -> I32
error_code_5 :: I32,
      -- | Error message
      Update -> T
error_message_5 :: T
    }
  | -- | The message content has changed 
  UpdateMessageContent
    { -- | Chat identifier 
      Update -> I32
chat_id_6 :: I53,
      -- | Message identifier 
      Update -> I32
message_id_6 :: I53,
      -- | New message content
      Update -> MessageContent
new_content_6 :: MessageContent
    }
  | -- | A message was edited. Changes in the message content will come in a separate updateMessageContent 
  UpdateMessageEdited
    { -- | Chat identifier 
      Update -> I32
chat_id_7 :: I53,
      -- | Message identifier 
      Update -> I32
message_id_7 :: I53,
      -- | Point in time (Unix timestamp) when the message was edited 
      Update -> I32
edit_date_7 :: I32,
      -- | New message reply markup; may be null
      Update -> ReplyMarkup
reply_markup_7 :: ReplyMarkup
    }
  | -- | The view count of the message has changed 
  UpdateMessageViews
    { -- | Chat identifier 
      Update -> I32
chat_id_8 :: I53,
      -- | Message identifier 
      Update -> I32
message_id_8 :: I53,
      -- | New value of the view count
      Update -> I32
views_8 :: I32
    }
  | -- | The message content was opened. Updates voice note messages to "listened", video note messages to "viewed" and starts the TTL timer for self-destructing messages 
  UpdateMessageContentOpened
    { -- | Chat identifier 
      Update -> I32
chat_id_9 :: I53,
      -- | Message identifier
      Update -> I32
message_id_9 :: I53
    }
  | -- | A message with an unread mention was read 
  UpdateMessageMentionRead
    { -- | Chat identifier 
      Update -> I32
chat_id_10 :: I53,
      -- | Message identifier 
      Update -> I32
message_id_10 :: I53,
      -- | The new number of unread mention messages left in the chat
      Update -> I32
unread_mention_count_10 :: I32
    }
  | -- | A message with a live location was viewed. When the update is received, the client is supposed to update the live location
  UpdateMessageLiveLocationViewed
    { -- | Identifier of the chat with the live location message 
      Update -> I32
chat_id_11 :: I53,
      -- | Identifier of the message with live location
      Update -> I32
message_id_11 :: I53
    }
  | -- | A new chat has been loaded/created. This update is guaranteed to come before the chat identifier is returned to the client. The chat field changes will be reported through separate updates 
  UpdateNewChat
    { -- | The chat
      Update -> Chat
chat_12 :: Chat
    }
  | -- | The list to which the chat belongs was changed. This update is guaranteed to be sent only when chat.order == 0 and the current or the new chat list is null 
  UpdateChatChatList
    { -- | Chat identifier 
      Update -> I32
chat_id_13 :: I53,
      -- | The new chat's chat list; may be null
      Update -> ChatList
chat_list_13 :: ChatList
    }
  | -- | The title of a chat was changed 
  UpdateChatTitle
    { -- | Chat identifier 
      Update -> I32
chat_id_14 :: I53,
      -- | The new chat title
      Update -> T
title_14 :: T
    }
  | -- | A chat photo was changed 
  UpdateChatPhoto
    { -- | Chat identifier 
      Update -> I32
chat_id_15 :: I53,
      -- | The new chat photo; may be null
      Update -> ChatPhoto
photo_15 :: ChatPhoto
    }
  | -- | Chat permissions was changed 
  UpdateChatPermissions
    { -- | Chat identifier 
      Update -> I32
chat_id_16 :: I53,
      -- | The new chat permissions
      Update -> ChatPermissions
permissions_16 :: ChatPermissions
    }
  | -- | The last message of a chat was changed. If last_message is null, then the last message in the chat became unknown. Some new unknown messages might be added to the chat in this case 
  UpdateChatLastMessage
    { -- | Chat identifier 
      Update -> I32
chat_id_17 :: I53,
      -- | The new last message in the chat; may be null 
      Update -> Message
last_message_17 :: Message,
      -- | New value of the chat order
      Update -> I64
order_17 :: I64
    }
  | -- | The order of the chat in the chat list has changed. Instead of this update updateChatLastMessage, updateChatIsPinned, updateChatDraftMessage, or updateChatSource might be sent 
  UpdateChatOrder
    { -- | Chat identifier 
      Update -> I32
chat_id_18 :: I53,
      -- | New value of the order
      Update -> I64
order_18 :: I64
    }
  | -- | A chat was pinned or unpinned 
  UpdateChatIsPinned
    { -- | Chat identifier 
      Update -> I32
chat_id_19 :: I53,
      -- | New value of is_pinned 
      Update -> Bool
is_pinned_19 :: Bool,
      -- | New value of the chat order
      Update -> I64
order_19 :: I64
    }
  | -- | A chat was marked as unread or was read 
  UpdateChatIsMarkedAsUnread
    { -- | Chat identifier 
      Update -> I32
chat_id_20 :: I53,
      -- | New value of is_marked_as_unread
      Update -> Bool
is_marked_as_unread_20 :: Bool
    }
  | -- | A chat's source in the chat list has changed 
  UpdateChatSource
    { -- | Chat identifier 
      Update -> I32
chat_id_21 :: I53,
      -- | New chat's source; may be null 
      Update -> ChatSource
source_21 :: ChatSource,
      -- | New value of chat order
      Update -> I64
order_21 :: I64
    }
  | -- | A chat's has_scheduled_messages field has changed 
  UpdateChatHasScheduledMessages
    { -- | Chat identifier 
      Update -> I32
chat_id_22 :: I53,
      -- | New value of has_scheduled_messages
      Update -> Bool
has_scheduled_messages_22 :: Bool
    }
  | -- | The value of the default disable_notification parameter, used when a message is sent to the chat, was changed 
  UpdateChatDefaultDisableNotification
    { -- | Chat identifier 
      Update -> I32
chat_id_23 :: I53,
      -- | The new default_disable_notification value
      Update -> Bool
default_disable_notification_23 :: Bool
    }
  | -- | Incoming messages were read or number of unread messages has been changed 
  UpdateChatReadInbox
    { -- | Chat identifier 
      Update -> I32
chat_id_24 :: I53,
      -- | Identifier of the last read incoming message 
      Update -> I32
last_read_inbox_message_id_24 :: I53,
      -- | The number of unread messages left in the chat
      Update -> I32
unread_count_24 :: I32
    }
  | -- | Outgoing messages were read 
  UpdateChatReadOutbox
    { -- | Chat identifier 
      Update -> I32
chat_id_25 :: I53,
      -- | Identifier of last read outgoing message
      Update -> I32
last_read_outbox_message_id_25 :: I53
    }
  | -- | The chat unread_mention_count has changed 
  UpdateChatUnreadMentionCount
    { -- | Chat identifier 
      Update -> I32
chat_id_26 :: I53,
      -- | The number of unread mention messages left in the chat
      Update -> I32
unread_mention_count_26 :: I32
    }
  | -- | Notification settings for a chat were changed 
  UpdateChatNotificationSettings
    { -- | Chat identifier 
      Update -> I32
chat_id_27 :: I53,
      -- | The new notification settings
      Update -> ChatNotificationSettings
notification_settings_27 :: ChatNotificationSettings
    }
  | -- | Notification settings for some type of chats were updated 
  UpdateScopeNotificationSettings
    { -- | Types of chats for which notification settings were updated 
      Update -> NotificationSettingsScope
scope_28 :: NotificationSettingsScope,
      -- | The new notification settings
      Update -> ScopeNotificationSettings
notification_settings_28 :: ScopeNotificationSettings
    }
  | -- | The chat action bar was changed 
  UpdateChatActionBar
    { -- | Chat identifier 
      Update -> I32
chat_id_29 :: I53,
      -- | The new value of the action bar; may be null
      Update -> ChatActionBar
action_bar_29 :: ChatActionBar
    }
  | -- | The chat pinned message was changed 
  UpdateChatPinnedMessage
    { -- | Chat identifier 
      Update -> I32
chat_id_30 :: I53,
      -- | The new identifier of the pinned message; 0 if there is no pinned message in the chat
      Update -> I32
pinned_message_id_30 :: I53
    }
  | -- | The default chat reply markup was changed. Can occur because new messages with reply markup were received or because an old reply markup was hidden by the user
  UpdateChatReplyMarkup
    { -- | Chat identifier 
      Update -> I32
chat_id_31 :: I53,
      -- | Identifier of the message from which reply markup needs to be used; 0 if there is no default custom reply markup in the chat
      Update -> I32
reply_markup_message_id_31 :: I53
    }
  | -- | A chat draft has changed. Be aware that the update may come in the currently opened chat but with old content of the draft. If the user has changed the content of the draft, this update shouldn't be applied 
  UpdateChatDraftMessage
    { -- | Chat identifier 
      Update -> I32
chat_id_32 :: I53,
      -- | The new draft message; may be null 
      Update -> DraftMessage
draft_message_32 :: DraftMessage,
      -- | New value of the chat order
      Update -> I64
order_32 :: I64
    }
  | -- | The number of online group members has changed. This update with non-zero count is sent only for currently opened chats. There is no guarantee that it will be sent just after the count has changed 
  UpdateChatOnlineMemberCount
    { -- | Identifier of the chat 
      Update -> I32
chat_id_33 :: I53,
      -- | New number of online members in the chat, or 0 if unknown
      Update -> I32
online_member_count_33 :: I32
    }
  | -- | A notification was changed 
  UpdateNotification
    { -- | Unique notification group identifier 
      Update -> I32
notification_group_id_34 :: I32,
      -- | Changed notification
      Update -> Notification
notification_34 :: Notification
    }
  | -- | A list of active notifications in a notification group has changed
  UpdateNotificationGroup
    { -- | Unique notification group identifier
      Update -> I32
notification_group_id_35 :: I32,
      -- | New type of the notification group
      Update -> NotificationGroupType
type_35 :: NotificationGroupType,
      -- | Identifier of a chat to which all notifications in the group belong
      Update -> I32
chat_id_35 :: I53,
      -- | Chat identifier, which notification settings must be applied to the added notifications
      Update -> I32
notification_settings_chat_id_35 :: I53,
      -- | True, if the notifications should be shown without sound
      Update -> Bool
is_silent_35 :: Bool,
      -- | Total number of unread notifications in the group, can be bigger than number of active notifications
      Update -> I32
total_count_35 :: I32,
      -- | List of added group notifications, sorted by notification ID 
      Update -> [Notification]
added_notifications_35 :: ([]) (Notification),
      -- | Identifiers of removed group notifications, sorted by notification ID
      Update -> [I32]
removed_notification_ids_35 :: ([]) (I32)
    }
  | -- | Contains active notifications that was shown on previous application launches. This update is sent only if the message database is used. In that case it comes once before any updateNotification and updateNotificationGroup update 
  UpdateActiveNotifications
    { -- | Lists of active notification groups
      Update -> [NotificationGroup]
groups_36 :: ([]) (NotificationGroup)
    }
  | -- | Describes whether there are some pending notification updates. Can be used to prevent application from killing, while there are some pending notifications
  UpdateHavePendingNotifications
    { -- | True, if there are some delayed notification updates, which will be sent soon
      Update -> Bool
have_delayed_notifications_37 :: Bool,
      -- | True, if there can be some yet unreceived notifications, which are being fetched from the server
      Update -> Bool
have_unreceived_notifications_37 :: Bool
    }
  | -- | Some messages were deleted 
  UpdateDeleteMessages
    { -- | Chat identifier 
      Update -> I32
chat_id_38 :: I53,
      -- | Identifiers of the deleted messages
      Update -> [I32]
message_ids_38 :: ([]) (I53),
      -- | True, if the messages are permanently deleted by a user (as opposed to just becoming inaccessible)
      Update -> Bool
is_permanent_38 :: Bool,
      -- | True, if the messages are deleted only from the cache and can possibly be retrieved again in the future
      Update -> Bool
from_cache_38 :: Bool
    }
  | -- | User activity in the chat has changed 
  UpdateUserChatAction
    { -- | Chat identifier 
      Update -> I32
chat_id_39 :: I53,
      -- | Identifier of a user performing an action 
      Update -> I32
user_id_39 :: I32,
      -- | The action description
      Update -> ChatAction
action_39 :: ChatAction
    }
  | -- | The user went online or offline 
  UpdateUserStatus
    { -- | User identifier 
      Update -> I32
user_id_40 :: I32,
      -- | New status of the user
      Update -> UserStatus
status_40 :: UserStatus
    }
  | -- | Some data of a user has changed. This update is guaranteed to come before the user identifier is returned to the client 
  UpdateUser
    { -- | New data about the user
      Update -> User
user_41 :: User
    }
  | -- | Some data of a basic group has changed. This update is guaranteed to come before the basic group identifier is returned to the client 
  UpdateBasicGroup
    { -- | New data about the group
      Update -> BasicGroup
basic_group_42 :: BasicGroup
    }
  | -- | Some data of a supergroup or a channel has changed. This update is guaranteed to come before the supergroup identifier is returned to the client 
  UpdateSupergroup
    { -- | New data about the supergroup
      Update -> Supergroup
supergroup_43 :: Supergroup
    }
  | -- | Some data of a secret chat has changed. This update is guaranteed to come before the secret chat identifier is returned to the client 
  UpdateSecretChat
    { -- | New data about the secret chat
      Update -> SecretChat
secret_chat_44 :: SecretChat
    }
  | -- | Some data from userFullInfo has been changed 
  UpdateUserFullInfo
    { -- | User identifier 
      Update -> I32
user_id_45 :: I32,
      -- | New full information about the user
      Update -> UserFullInfo
user_full_info_45 :: UserFullInfo
    }
  | -- | Some data from basicGroupFullInfo has been changed 
  UpdateBasicGroupFullInfo
    { -- | Identifier of a basic group 
      Update -> I32
basic_group_id_46 :: I32,
      -- | New full information about the group
      Update -> BasicGroupFullInfo
basic_group_full_info_46 :: BasicGroupFullInfo
    }
  | -- | Some data from supergroupFullInfo has been changed 
  UpdateSupergroupFullInfo
    { -- | Identifier of the supergroup or channel 
      Update -> I32
supergroup_id_47 :: I32,
      -- | New full information about the supergroup
      Update -> SupergroupFullInfo
supergroup_full_info_47 :: SupergroupFullInfo
    }
  | -- | Service notification from the server. Upon receiving this the client must show a popup with the content of the notification
  UpdateServiceNotification
    { -- | Notification type. If type begins with "AUTH_KEY_DROP_", then two buttons "Cancel" and "Log out" should be shown under notification; if user presses the second, all local data should be destroyed using Destroy method
      Update -> T
type_48 :: T,
      -- | Notification content
      Update -> MessageContent
content_48 :: MessageContent
    }
  | -- | Information about a file was updated 
  UpdateFile
    { -- | New data about the file
      Update -> File
file_49 :: File
    }
  | -- | The file generation process needs to be started by the client
  UpdateFileGenerationStart
    { -- | Unique identifier for the generation process
      Update -> I64
generation_id_50 :: I64,
      -- | The path to a file from which a new file is generated; may be empty
      Update -> T
original_path_50 :: T,
      -- | The path to a file that should be created and where the new file should be generated
      Update -> T
destination_path_50 :: T,
      -- | String specifying the conversion applied to the original file. If conversion is "#url#" than original_path contains an HTTP/HTTPS URL of a file, which should be downloaded by the client
      Update -> T
conversion_50 :: T
    }
  | -- | File generation is no longer needed 
  UpdateFileGenerationStop
    { -- | Unique identifier for the generation process
      Update -> I64
generation_id_51 :: I64
    }
  | -- | New call was created or information about a call was updated 
  UpdateCall
    { -- | New data about a call
      Update -> Call
call_52 :: Call
    }
  | -- | Some privacy setting rules have been changed 
  UpdateUserPrivacySettingRules
    { -- | The privacy setting 
      Update -> UserPrivacySetting
setting_53 :: UserPrivacySetting,
      -- | New privacy rules
      Update -> UserPrivacySettingRules
rules_53 :: UserPrivacySettingRules
    }
  | -- | Number of unread messages in a chat list has changed. This update is sent only if the message database is used 
  UpdateUnreadMessageCount
    { -- | The chat list with changed number of unread messages
      Update -> ChatList
chat_list_54 :: ChatList,
      -- | Total number of unread messages 
      Update -> I32
unread_count_54 :: I32,
      -- | Total number of unread messages in unmuted chats
      Update -> I32
unread_unmuted_count_54 :: I32
    }
  | -- | Number of unread chats, i.e. with unread messages or marked as unread, has changed. This update is sent only if the message database is used
  UpdateUnreadChatCount
    { -- | The chat list with changed number of unread messages
      Update -> ChatList
chat_list_55 :: ChatList,
      -- | Approximate total number of chats in the chat list
      Update -> I32
total_count_55 :: I32,
      -- | Total number of unread chats 
      Update -> I32
unread_count_55 :: I32,
      -- | Total number of unread unmuted chats
      Update -> I32
unread_unmuted_count_55 :: I32,
      -- | Total number of chats marked as unread 
      Update -> I32
marked_as_unread_count_55 :: I32,
      -- | Total number of unmuted chats marked as unread
      Update -> I32
marked_as_unread_unmuted_count_55 :: I32
    }
  | -- | An option changed its value 
  UpdateOption
    { -- | The option name 
      Update -> T
name_56 :: T,
      -- | The new option value
      Update -> OptionValue
value_56 :: OptionValue
    }
  | -- | A sticker set has changed 
  UpdateStickerSet
    { -- | The sticker set
      Update -> StickerSet
sticker_set_57 :: StickerSet
    }
  | -- | The list of installed sticker sets was updated 
  UpdateInstalledStickerSets
    { -- | True, if the list of installed mask sticker sets was updated 
      Update -> Bool
is_masks_58 :: Bool,
      -- | The new list of installed ordinary sticker sets
      Update -> [I64]
sticker_set_ids_58 :: ([]) (I64)
    }
  | -- | The list of trending sticker sets was updated or some of them were viewed 
  UpdateTrendingStickerSets
    { -- | The prefix of the list of trending sticker sets with the newest trending sticker sets
      Update -> StickerSets
sticker_sets_59 :: StickerSets
    }
  | -- | The list of recently used stickers was updated 
  UpdateRecentStickers
    { -- | True, if the list of stickers attached to photo or video files was updated, otherwise the list of sent stickers is updated 
      Update -> Bool
is_attached_60 :: Bool,
      -- | The new list of file identifiers of recently used stickers
      Update -> [I32]
sticker_ids_60 :: ([]) (I32)
    }
  | -- | The list of favorite stickers was updated 
  UpdateFavoriteStickers
    { -- | The new list of file identifiers of favorite stickers
      Update -> [I32]
sticker_ids_61 :: ([]) (I32)
    }
  | -- | The list of saved animations was updated 
  UpdateSavedAnimations
    { -- | The new list of file identifiers of saved animations
      Update -> [I32]
animation_ids_62 :: ([]) (I32)
    }
  | -- | The selected background has changed 
  UpdateSelectedBackground
    { -- | True, if background for dark theme has changed 
      Update -> Bool
for_dark_theme_63 :: Bool,
      -- | The new selected background; may be null
      Update -> Background
background_63 :: Background
    }
  | -- | Some language pack strings have been updated 
  UpdateLanguagePackStrings
    { -- | Localization target to which the language pack belongs 
      Update -> T
localization_target_64 :: T,
      -- | Identifier of the updated language pack 
      Update -> T
language_pack_id_64 :: T,
      -- | List of changed language pack strings
      Update -> [LanguagePackString]
strings_64 :: ([]) (LanguagePackString)
    }
  | -- | The connection state has changed 
  UpdateConnectionState
    { -- | The new connection state
      Update -> ConnectionState
state_65 :: ConnectionState
    }
  | -- | New terms of service must be accepted by the user. If the terms of service are declined, then the deleteAccount method should be called with the reason "Decline ToS update" 
  UpdateTermsOfService
    { -- | Identifier of the terms of service 
      Update -> T
terms_of_service_id_66 :: T,
      -- | The new terms of service
      Update -> TermsOfService
terms_of_service_66 :: TermsOfService
    }
  | -- | The list of users nearby has changed. The update is sent only 60 seconds after a successful searchChatsNearby request 
  UpdateUsersNearby
    { -- | The new list of users nearby
      Update -> [ChatNearby]
users_nearby_67 :: ([]) (ChatNearby)
    }
  | -- | The list of supported dice emojis has changed 
  UpdateDiceEmojis
    { -- | The new list of supported dice emojis
      Update -> [T]
emojis_68 :: ([]) (T)
    }
  | -- | A new incoming inline query; for bots only 
  UpdateNewInlineQuery
    { -- | Unique query identifier 
      Update -> I64
id_69 :: I64,
      -- | Identifier of the user who sent the query 
      Update -> I32
sender_user_id_69 :: I32,
      -- | User location, provided by the client; may be null
      Update -> Location
user_location_69 :: Location,
      -- | Text of the query 
      Update -> T
query_69 :: T,
      -- | Offset of the first entry to return
      Update -> T
offset_69 :: T
    }
  | -- | The user has chosen a result of an inline query; for bots only 
  UpdateNewChosenInlineResult
    { -- | Identifier of the user who sent the query 
      Update -> I32
sender_user_id_70 :: I32,
      -- | User location, provided by the client; may be null
      Update -> Location
user_location_70 :: Location,
      -- | Text of the query 
      Update -> T
query_70 :: T,
      -- | Identifier of the chosen result 
      Update -> T
result_id_70 :: T,
      -- | Identifier of the sent inline message, if known
      Update -> T
inline_message_id_70 :: T
    }
  | -- | A new incoming callback query; for bots only 
  UpdateNewCallbackQuery
    { -- | Unique query identifier 
      Update -> I64
id_71 :: I64,
      -- | Identifier of the user who sent the query
      Update -> I32
sender_user_id_71 :: I32,
      -- | Identifier of the chat where the query was sent 
      Update -> I32
chat_id_71 :: I53,
      -- | Identifier of the message, from which the query originated
      Update -> I32
message_id_71 :: I53,
      -- | Identifier that uniquely corresponds to the chat to which the message was sent 
      Update -> I64
chat_instance_71 :: I64,
      -- | Query payload
      Update -> CallbackQueryPayload
payload_71 :: CallbackQueryPayload
    }
  | -- | A new incoming callback query from a message sent via a bot; for bots only 
  UpdateNewInlineCallbackQuery
    { -- | Unique query identifier 
      Update -> I64
id_72 :: I64,
      -- | Identifier of the user who sent the query 
      Update -> I32
sender_user_id_72 :: I32,
      -- | Identifier of the inline message, from which the query originated
      Update -> T
inline_message_id_72 :: T,
      -- | An identifier uniquely corresponding to the chat a message was sent to 
      Update -> I64
chat_instance_72 :: I64,
      -- | Query payload
      Update -> CallbackQueryPayload
payload_72 :: CallbackQueryPayload
    }
  | -- | A new incoming shipping query; for bots only. Only for invoices with flexible price 
  UpdateNewShippingQuery
    { -- | Unique query identifier 
      Update -> I64
id_73 :: I64,
      -- | Identifier of the user who sent the query 
      Update -> I32
sender_user_id_73 :: I32,
      -- | Invoice payload 
      Update -> T
invoice_payload_73 :: T,
      -- | User shipping address
      Update -> Address
shipping_address_73 :: Address
    }
  | -- | A new incoming pre-checkout query; for bots only. Contains full information about a checkout 
  UpdateNewPreCheckoutQuery
    { -- | Unique query identifier 
      Update -> I64
id_74 :: I64,
      -- | Identifier of the user who sent the query 
      Update -> I32
sender_user_id_74 :: I32,
      -- | Currency for the product price 
      Update -> T
currency_74 :: T,
      -- | Total price for the product, in the minimal quantity of the currency
      Update -> I32
total_amount_74 :: I53,
      -- | Invoice payload 
      Update -> ByteString64
invoice_payload_74 :: ByteString64,
      -- | Identifier of a shipping option chosen by the user; may be empty if not applicable 
      Update -> T
shipping_option_id_74 :: T,
      -- | Information about the order; may be null
      Update -> OrderInfo
order_info_74 :: OrderInfo
    }
  | -- | A new incoming event; for bots only 
  UpdateNewCustomEvent
    { -- | A JSON-serialized event
      Update -> T
event_75 :: T
    }
  | -- | A new incoming query; for bots only 
  UpdateNewCustomQuery
    { -- | The query identifier 
      Update -> I64
id_76 :: I64,
      -- | JSON-serialized query data 
      Update -> T
data_76 :: T,
      -- | Query timeout
      Update -> I32
timeout_76 :: I32
    }
  | -- | A poll was updated; for bots only 
  UpdatePoll
    { -- | New data about the poll
      Update -> Poll
poll_77 :: Poll
    }
  | -- | A user changed the answer to a poll; for bots only 
  UpdatePollAnswer
    { -- | Unique poll identifier 
      Update -> I64
poll_id_78 :: I64,
      -- | The user, who changed the answer to the poll 
      Update -> I32
user_id_78 :: I32,
      -- | 0-based identifiers of answer options, chosen by the user
      Update -> [I32]
option_ids_78 :: ([]) (I32)
    }
  deriving (I32 -> Update -> ShowS
[Update] -> ShowS
Update -> String
(I32 -> Update -> ShowS)
-> (Update -> String) -> ([Update] -> ShowS) -> Show Update
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Update] -> ShowS
$cshowList :: [Update] -> ShowS
show :: Update -> String
$cshow :: Update -> String
showsPrec :: I32 -> Update -> ShowS
$cshowsPrec :: I32 -> Update -> ShowS
Show, Update -> Update -> Bool
(Update -> Update -> Bool)
-> (Update -> Update -> Bool) -> Eq Update
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Update -> Update -> Bool
$c/= :: Update -> Update -> Bool
== :: Update -> Update -> Bool
$c== :: Update -> Update -> Bool
Eq, (forall x. Update -> Rep Update x)
-> (forall x. Rep Update x -> Update) -> Generic Update
forall x. Rep Update x -> Update
forall x. Update -> Rep Update x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Update x -> Update
$cfrom :: forall x. Update -> Rep Update x
Generic)
data Updates
  = -- | Contains a list of updates 
  Updates
    { -- | List of updates
      Updates -> [Update]
updates_1 :: ([]) (Update)
    }
  deriving (I32 -> Updates -> ShowS
[Updates] -> ShowS
Updates -> String
(I32 -> Updates -> ShowS)
-> (Updates -> String) -> ([Updates] -> ShowS) -> Show Updates
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Updates] -> ShowS
$cshowList :: [Updates] -> ShowS
show :: Updates -> String
$cshow :: Updates -> String
showsPrec :: I32 -> Updates -> ShowS
$cshowsPrec :: I32 -> Updates -> ShowS
Show, Updates -> Updates -> Bool
(Updates -> Updates -> Bool)
-> (Updates -> Updates -> Bool) -> Eq Updates
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Updates -> Updates -> Bool
$c/= :: Updates -> Updates -> Bool
== :: Updates -> Updates -> Bool
$c== :: Updates -> Updates -> Bool
Eq, (forall x. Updates -> Rep Updates x)
-> (forall x. Rep Updates x -> Updates) -> Generic Updates
forall x. Rep Updates x -> Updates
forall x. Updates -> Rep Updates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Updates x -> Updates
$cfrom :: forall x. Updates -> Rep Updates x
Generic)
-- | Describes a stream to which TDLib internal log is written
data LogStream
  = -- | The log is written to stderr or an OS specific log
  LogStreamDefault
    { 
    }
  | -- | The log is written to a file 
  LogStreamFile
    { -- | Path to the file to where the internal TDLib log will be written 
      LogStream -> T
path_2 :: T,
      -- | The maximum size of the file to where the internal TDLib log is written before the file will be auto-rotated
      LogStream -> I32
max_file_size_2 :: I53
    }
  | -- | The log is written nowhere
  LogStreamEmpty
    { 
    }
  deriving (I32 -> LogStream -> ShowS
[LogStream] -> ShowS
LogStream -> String
(I32 -> LogStream -> ShowS)
-> (LogStream -> String)
-> ([LogStream] -> ShowS)
-> Show LogStream
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogStream] -> ShowS
$cshowList :: [LogStream] -> ShowS
show :: LogStream -> String
$cshow :: LogStream -> String
showsPrec :: I32 -> LogStream -> ShowS
$cshowsPrec :: I32 -> LogStream -> ShowS
Show, LogStream -> LogStream -> Bool
(LogStream -> LogStream -> Bool)
-> (LogStream -> LogStream -> Bool) -> Eq LogStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogStream -> LogStream -> Bool
$c/= :: LogStream -> LogStream -> Bool
== :: LogStream -> LogStream -> Bool
$c== :: LogStream -> LogStream -> Bool
Eq, (forall x. LogStream -> Rep LogStream x)
-> (forall x. Rep LogStream x -> LogStream) -> Generic LogStream
forall x. Rep LogStream x -> LogStream
forall x. LogStream -> Rep LogStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogStream x -> LogStream
$cfrom :: forall x. LogStream -> Rep LogStream x
Generic)
data LogVerbosityLevel
  = -- | Contains a TDLib internal log verbosity level 
  LogVerbosityLevel
    { -- | Log verbosity level
      LogVerbosityLevel -> I32
verbosity_level_1 :: I32
    }
  deriving (I32 -> LogVerbosityLevel -> ShowS
[LogVerbosityLevel] -> ShowS
LogVerbosityLevel -> String
(I32 -> LogVerbosityLevel -> ShowS)
-> (LogVerbosityLevel -> String)
-> ([LogVerbosityLevel] -> ShowS)
-> Show LogVerbosityLevel
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogVerbosityLevel] -> ShowS
$cshowList :: [LogVerbosityLevel] -> ShowS
show :: LogVerbosityLevel -> String
$cshow :: LogVerbosityLevel -> String
showsPrec :: I32 -> LogVerbosityLevel -> ShowS
$cshowsPrec :: I32 -> LogVerbosityLevel -> ShowS
Show, LogVerbosityLevel -> LogVerbosityLevel -> Bool
(LogVerbosityLevel -> LogVerbosityLevel -> Bool)
-> (LogVerbosityLevel -> LogVerbosityLevel -> Bool)
-> Eq LogVerbosityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogVerbosityLevel -> LogVerbosityLevel -> Bool
$c/= :: LogVerbosityLevel -> LogVerbosityLevel -> Bool
== :: LogVerbosityLevel -> LogVerbosityLevel -> Bool
$c== :: LogVerbosityLevel -> LogVerbosityLevel -> Bool
Eq, (forall x. LogVerbosityLevel -> Rep LogVerbosityLevel x)
-> (forall x. Rep LogVerbosityLevel x -> LogVerbosityLevel)
-> Generic LogVerbosityLevel
forall x. Rep LogVerbosityLevel x -> LogVerbosityLevel
forall x. LogVerbosityLevel -> Rep LogVerbosityLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogVerbosityLevel x -> LogVerbosityLevel
$cfrom :: forall x. LogVerbosityLevel -> Rep LogVerbosityLevel x
Generic)
data LogTags
  = -- | Contains a list of available TDLib internal log tags 
  LogTags
    { -- | List of log tags
      LogTags -> [T]
tags_1 :: ([]) (T)
    }
  deriving (I32 -> LogTags -> ShowS
[LogTags] -> ShowS
LogTags -> String
(I32 -> LogTags -> ShowS)
-> (LogTags -> String) -> ([LogTags] -> ShowS) -> Show LogTags
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogTags] -> ShowS
$cshowList :: [LogTags] -> ShowS
show :: LogTags -> String
$cshow :: LogTags -> String
showsPrec :: I32 -> LogTags -> ShowS
$cshowsPrec :: I32 -> LogTags -> ShowS
Show, LogTags -> LogTags -> Bool
(LogTags -> LogTags -> Bool)
-> (LogTags -> LogTags -> Bool) -> Eq LogTags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogTags -> LogTags -> Bool
$c/= :: LogTags -> LogTags -> Bool
== :: LogTags -> LogTags -> Bool
$c== :: LogTags -> LogTags -> Bool
Eq, (forall x. LogTags -> Rep LogTags x)
-> (forall x. Rep LogTags x -> LogTags) -> Generic LogTags
forall x. Rep LogTags x -> LogTags
forall x. LogTags -> Rep LogTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogTags x -> LogTags
$cfrom :: forall x. LogTags -> Rep LogTags x
Generic)
data TestInt
  = -- | A simple object containing a number; for testing only 
  TestInt
    { -- | Number
      TestInt -> I32
value_1 :: I32
    }
  deriving (I32 -> TestInt -> ShowS
[TestInt] -> ShowS
TestInt -> String
(I32 -> TestInt -> ShowS)
-> (TestInt -> String) -> ([TestInt] -> ShowS) -> Show TestInt
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestInt] -> ShowS
$cshowList :: [TestInt] -> ShowS
show :: TestInt -> String
$cshow :: TestInt -> String
showsPrec :: I32 -> TestInt -> ShowS
$cshowsPrec :: I32 -> TestInt -> ShowS
Show, TestInt -> TestInt -> Bool
(TestInt -> TestInt -> Bool)
-> (TestInt -> TestInt -> Bool) -> Eq TestInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestInt -> TestInt -> Bool
$c/= :: TestInt -> TestInt -> Bool
== :: TestInt -> TestInt -> Bool
$c== :: TestInt -> TestInt -> Bool
Eq, (forall x. TestInt -> Rep TestInt x)
-> (forall x. Rep TestInt x -> TestInt) -> Generic TestInt
forall x. Rep TestInt x -> TestInt
forall x. TestInt -> Rep TestInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestInt x -> TestInt
$cfrom :: forall x. TestInt -> Rep TestInt x
Generic)
data TestString
  = -- | A simple object containing a string; for testing only 
  TestString
    { -- | String
      TestString -> T
value_1 :: T
    }
  deriving (I32 -> TestString -> ShowS
[TestString] -> ShowS
TestString -> String
(I32 -> TestString -> ShowS)
-> (TestString -> String)
-> ([TestString] -> ShowS)
-> Show TestString
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestString] -> ShowS
$cshowList :: [TestString] -> ShowS
show :: TestString -> String
$cshow :: TestString -> String
showsPrec :: I32 -> TestString -> ShowS
$cshowsPrec :: I32 -> TestString -> ShowS
Show, TestString -> TestString -> Bool
(TestString -> TestString -> Bool)
-> (TestString -> TestString -> Bool) -> Eq TestString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestString -> TestString -> Bool
$c/= :: TestString -> TestString -> Bool
== :: TestString -> TestString -> Bool
$c== :: TestString -> TestString -> Bool
Eq, (forall x. TestString -> Rep TestString x)
-> (forall x. Rep TestString x -> TestString) -> Generic TestString
forall x. Rep TestString x -> TestString
forall x. TestString -> Rep TestString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestString x -> TestString
$cfrom :: forall x. TestString -> Rep TestString x
Generic)
data TestBytes
  = -- | A simple object containing a sequence of bytes; for testing only 
  TestBytes
    { -- | Bytes
      TestBytes -> ByteString64
value_1 :: ByteString64
    }
  deriving (I32 -> TestBytes -> ShowS
[TestBytes] -> ShowS
TestBytes -> String
(I32 -> TestBytes -> ShowS)
-> (TestBytes -> String)
-> ([TestBytes] -> ShowS)
-> Show TestBytes
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestBytes] -> ShowS
$cshowList :: [TestBytes] -> ShowS
show :: TestBytes -> String
$cshow :: TestBytes -> String
showsPrec :: I32 -> TestBytes -> ShowS
$cshowsPrec :: I32 -> TestBytes -> ShowS
Show, TestBytes -> TestBytes -> Bool
(TestBytes -> TestBytes -> Bool)
-> (TestBytes -> TestBytes -> Bool) -> Eq TestBytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestBytes -> TestBytes -> Bool
$c/= :: TestBytes -> TestBytes -> Bool
== :: TestBytes -> TestBytes -> Bool
$c== :: TestBytes -> TestBytes -> Bool
Eq, (forall x. TestBytes -> Rep TestBytes x)
-> (forall x. Rep TestBytes x -> TestBytes) -> Generic TestBytes
forall x. Rep TestBytes x -> TestBytes
forall x. TestBytes -> Rep TestBytes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestBytes x -> TestBytes
$cfrom :: forall x. TestBytes -> Rep TestBytes x
Generic)
data TestVectorInt
  = -- | A simple object containing a vector of numbers; for testing only 
  TestVectorInt
    { -- | Vector of numbers
      TestVectorInt -> [I32]
value_1 :: ([]) (I32)
    }
  deriving (I32 -> TestVectorInt -> ShowS
[TestVectorInt] -> ShowS
TestVectorInt -> String
(I32 -> TestVectorInt -> ShowS)
-> (TestVectorInt -> String)
-> ([TestVectorInt] -> ShowS)
-> Show TestVectorInt
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestVectorInt] -> ShowS
$cshowList :: [TestVectorInt] -> ShowS
show :: TestVectorInt -> String
$cshow :: TestVectorInt -> String
showsPrec :: I32 -> TestVectorInt -> ShowS
$cshowsPrec :: I32 -> TestVectorInt -> ShowS
Show, TestVectorInt -> TestVectorInt -> Bool
(TestVectorInt -> TestVectorInt -> Bool)
-> (TestVectorInt -> TestVectorInt -> Bool) -> Eq TestVectorInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestVectorInt -> TestVectorInt -> Bool
$c/= :: TestVectorInt -> TestVectorInt -> Bool
== :: TestVectorInt -> TestVectorInt -> Bool
$c== :: TestVectorInt -> TestVectorInt -> Bool
Eq, (forall x. TestVectorInt -> Rep TestVectorInt x)
-> (forall x. Rep TestVectorInt x -> TestVectorInt)
-> Generic TestVectorInt
forall x. Rep TestVectorInt x -> TestVectorInt
forall x. TestVectorInt -> Rep TestVectorInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestVectorInt x -> TestVectorInt
$cfrom :: forall x. TestVectorInt -> Rep TestVectorInt x
Generic)
data TestVectorIntObject
  = -- | A simple object containing a vector of objects that hold a number; for testing only 
  TestVectorIntObject
    { -- | Vector of objects
      TestVectorIntObject -> [TestInt]
value_1 :: ([]) (TestInt)
    }
  deriving (I32 -> TestVectorIntObject -> ShowS
[TestVectorIntObject] -> ShowS
TestVectorIntObject -> String
(I32 -> TestVectorIntObject -> ShowS)
-> (TestVectorIntObject -> String)
-> ([TestVectorIntObject] -> ShowS)
-> Show TestVectorIntObject
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestVectorIntObject] -> ShowS
$cshowList :: [TestVectorIntObject] -> ShowS
show :: TestVectorIntObject -> String
$cshow :: TestVectorIntObject -> String
showsPrec :: I32 -> TestVectorIntObject -> ShowS
$cshowsPrec :: I32 -> TestVectorIntObject -> ShowS
Show, TestVectorIntObject -> TestVectorIntObject -> Bool
(TestVectorIntObject -> TestVectorIntObject -> Bool)
-> (TestVectorIntObject -> TestVectorIntObject -> Bool)
-> Eq TestVectorIntObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestVectorIntObject -> TestVectorIntObject -> Bool
$c/= :: TestVectorIntObject -> TestVectorIntObject -> Bool
== :: TestVectorIntObject -> TestVectorIntObject -> Bool
$c== :: TestVectorIntObject -> TestVectorIntObject -> Bool
Eq, (forall x. TestVectorIntObject -> Rep TestVectorIntObject x)
-> (forall x. Rep TestVectorIntObject x -> TestVectorIntObject)
-> Generic TestVectorIntObject
forall x. Rep TestVectorIntObject x -> TestVectorIntObject
forall x. TestVectorIntObject -> Rep TestVectorIntObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestVectorIntObject x -> TestVectorIntObject
$cfrom :: forall x. TestVectorIntObject -> Rep TestVectorIntObject x
Generic)
data TestVectorString
  = -- | A simple object containing a vector of strings; for testing only 
  TestVectorString
    { -- | Vector of strings
      TestVectorString -> [T]
value_1 :: ([]) (T)
    }
  deriving (I32 -> TestVectorString -> ShowS
[TestVectorString] -> ShowS
TestVectorString -> String
(I32 -> TestVectorString -> ShowS)
-> (TestVectorString -> String)
-> ([TestVectorString] -> ShowS)
-> Show TestVectorString
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestVectorString] -> ShowS
$cshowList :: [TestVectorString] -> ShowS
show :: TestVectorString -> String
$cshow :: TestVectorString -> String
showsPrec :: I32 -> TestVectorString -> ShowS
$cshowsPrec :: I32 -> TestVectorString -> ShowS
Show, TestVectorString -> TestVectorString -> Bool
(TestVectorString -> TestVectorString -> Bool)
-> (TestVectorString -> TestVectorString -> Bool)
-> Eq TestVectorString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestVectorString -> TestVectorString -> Bool
$c/= :: TestVectorString -> TestVectorString -> Bool
== :: TestVectorString -> TestVectorString -> Bool
$c== :: TestVectorString -> TestVectorString -> Bool
Eq, (forall x. TestVectorString -> Rep TestVectorString x)
-> (forall x. Rep TestVectorString x -> TestVectorString)
-> Generic TestVectorString
forall x. Rep TestVectorString x -> TestVectorString
forall x. TestVectorString -> Rep TestVectorString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestVectorString x -> TestVectorString
$cfrom :: forall x. TestVectorString -> Rep TestVectorString x
Generic)
data TestVectorStringObject
  = -- | A simple object containing a vector of objects that hold a string; for testing only 
  TestVectorStringObject
    { -- | Vector of objects
      TestVectorStringObject -> [TestString]
value_1 :: ([]) (TestString)
    }
  deriving (I32 -> TestVectorStringObject -> ShowS
[TestVectorStringObject] -> ShowS
TestVectorStringObject -> String
(I32 -> TestVectorStringObject -> ShowS)
-> (TestVectorStringObject -> String)
-> ([TestVectorStringObject] -> ShowS)
-> Show TestVectorStringObject
forall a.
(I32 -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestVectorStringObject] -> ShowS
$cshowList :: [TestVectorStringObject] -> ShowS
show :: TestVectorStringObject -> String
$cshow :: TestVectorStringObject -> String
showsPrec :: I32 -> TestVectorStringObject -> ShowS
$cshowsPrec :: I32 -> TestVectorStringObject -> ShowS
Show, TestVectorStringObject -> TestVectorStringObject -> Bool
(TestVectorStringObject -> TestVectorStringObject -> Bool)
-> (TestVectorStringObject -> TestVectorStringObject -> Bool)
-> Eq TestVectorStringObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestVectorStringObject -> TestVectorStringObject -> Bool
$c/= :: TestVectorStringObject -> TestVectorStringObject -> Bool
== :: TestVectorStringObject -> TestVectorStringObject -> Bool
$c== :: TestVectorStringObject -> TestVectorStringObject -> Bool
Eq, (forall x. TestVectorStringObject -> Rep TestVectorStringObject x)
-> (forall x.
    Rep TestVectorStringObject x -> TestVectorStringObject)
-> Generic TestVectorStringObject
forall x. Rep TestVectorStringObject x -> TestVectorStringObject
forall x. TestVectorStringObject -> Rep TestVectorStringObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestVectorStringObject x -> TestVectorStringObject
$cfrom :: forall x. TestVectorStringObject -> Rep TestVectorStringObject x
Generic)

[TestVectorStringObject] -> Encoding
[TestVectorStringObject] -> Value
[TestVectorString] -> Encoding
[TestVectorString] -> Value
[TestVectorIntObject] -> Encoding
[TestVectorIntObject] -> Value
[TestVectorInt] -> Encoding
[TestVectorInt] -> Value
[TestBytes] -> Encoding
[TestBytes] -> Value
[TestString] -> Encoding
[TestString] -> Value
[TestInt] -> Encoding
[TestInt] -> Value
[LogTags] -> Encoding
[LogTags] -> Value
[LogVerbosityLevel] -> Encoding
[LogVerbosityLevel] -> Value
[LogStream] -> Encoding
[LogStream] -> Value
[Updates] -> Encoding
[Updates] -> Value
[Update] -> Encoding
[Update] -> Value
[ChatStatistics] -> Encoding
[ChatStatistics] -> Value
[ChatStatisticsMessageInteractionCounters] -> Encoding
[ChatStatisticsMessageInteractionCounters] -> Value
[StatisticsGraph] -> Encoding
[StatisticsGraph] -> Value
[StatisticsValue] -> Encoding
[StatisticsValue] -> Value
[DateRange] -> Encoding
[DateRange] -> Value
[InputSticker] -> Encoding
[InputSticker] -> Value
[Proxies] -> Encoding
[Proxies] -> Value
[Proxy] -> Encoding
[Proxy] -> Value
[ProxyType] -> Encoding
[ProxyType] -> Value
[TextParseMode] -> Encoding
[TextParseMode] -> Value
[DeepLinkInfo] -> Encoding
[DeepLinkInfo] -> Value
[Seconds] -> Encoding
[Seconds] -> Value
[Text] -> Encoding
[Text] -> Value
[Count] -> Encoding
[Count] -> Value
[TMeUrls] -> Encoding
[TMeUrls] -> Value
[TMeUrl] -> Encoding
[TMeUrl] -> Value
[TMeUrlType] -> Encoding
[TMeUrlType] -> Value
[TopChatCategory] -> Encoding
[TopChatCategory] -> Value
[ConnectionState] -> Encoding
[ConnectionState] -> Value
[AutoDownloadSettingsPresets] -> Encoding
[AutoDownloadSettingsPresets] -> Value
[AutoDownloadSettings] -> Encoding
[AutoDownloadSettings] -> Value
[NetworkStatistics] -> Encoding
[NetworkStatistics] -> Value
[NetworkStatisticsEntry] -> Encoding
[NetworkStatisticsEntry] -> Value
[NetworkType] -> Encoding
[NetworkType] -> Value
[DatabaseStatistics] -> Encoding
[DatabaseStatistics] -> Value
[StorageStatisticsFast] -> Encoding
[StorageStatisticsFast] -> Value
[StorageStatistics] -> Encoding
[StorageStatistics] -> Value
[StorageStatisticsByChat] -> Encoding
[StorageStatisticsByChat] -> Value
[StorageStatisticsByFileType] -> Encoding
[StorageStatisticsByFileType] -> Value
[FileType] -> Encoding
[FileType] -> Value
[FilePart] -> Encoding
[FilePart] -> Value
[MessageLinkInfo] -> Encoding
[MessageLinkInfo] -> Value
[PublicMessageLink] -> Encoding
[PublicMessageLink] -> Value
[ChatReportReason] -> Encoding
[ChatReportReason] -> Value
[ConnectedWebsites] -> Encoding
[ConnectedWebsites] -> Value
[ConnectedWebsite] -> Encoding
[ConnectedWebsite] -> Value
[Sessions] -> Encoding
[Sessions] -> Value
[Session] -> Encoding
[Session] -> Value
[AccountTtl] -> Encoding
[AccountTtl] -> Value
[UserPrivacySetting] -> Encoding
[UserPrivacySetting] -> Value
[UserPrivacySettingRules] -> Encoding
[UserPrivacySettingRules] -> Value
[UserPrivacySettingRule] -> Encoding
[UserPrivacySettingRule] -> Value
[JsonValue] -> Encoding
[JsonValue] -> Value
[JsonObjectMember] -> Encoding
[JsonObjectMember] -> Value
[OptionValue] -> Encoding
[OptionValue] -> Value
[NotificationGroup] -> Encoding
[NotificationGroup] -> Value
[Notification] -> Encoding
[Notification] -> Value
[NotificationGroupType] -> Encoding
[NotificationGroupType] -> Value
[NotificationType] -> Encoding
[NotificationType] -> Value
[PushMessageContent] -> Encoding
[PushMessageContent] -> Value
[CheckChatUsernameResult] -> Encoding
[CheckChatUsernameResult] -> Value
[CanTransferOwnershipResult] -> Encoding
[CanTransferOwnershipResult] -> Value
[Hashtags] -> Encoding
[Hashtags] -> Value
[InputBackground] -> Encoding
[InputBackground] -> Value
[Backgrounds] -> Encoding
[Backgrounds] -> Value
[Background] -> Encoding
[Background] -> Value
[BackgroundType] -> Encoding
[BackgroundType] -> Value
[BackgroundFill] -> Encoding
[BackgroundFill] -> Value
[PushReceiverId] -> Encoding
[PushReceiverId] -> Value
[DeviceToken] -> Encoding
[DeviceToken] -> Value
[LocalizationTargetInfo] -> Encoding
[LocalizationTargetInfo] -> Value
[LanguagePackInfo] -> Encoding
[LanguagePackInfo] -> Value
[LanguagePackStrings] -> Encoding
[LanguagePackStrings] -> Value
[LanguagePackString] -> Encoding
[LanguagePackString] -> Value
[LanguagePackStringValue] -> Encoding
[LanguagePackStringValue] -> Value
[ChatEventLogFilters] -> Encoding
[ChatEventLogFilters] -> Value
[ChatEvents] -> Encoding
[ChatEvents] -> Value
[ChatEvent] -> Encoding
[ChatEvent] -> Value
[ChatEventAction] -> Encoding
[ChatEventAction] -> Value
[GameHighScores] -> Encoding
[GameHighScores] -> Value
[GameHighScore] -> Encoding
[GameHighScore] -> Value
[CustomRequestResult] -> Encoding
[CustomRequestResult] -> Value
[CallbackQueryAnswer] -> Encoding
[CallbackQueryAnswer] -> Value
[CallbackQueryPayload] -> Encoding
[CallbackQueryPayload] -> Value
[InlineQueryResults] -> Encoding
[InlineQueryResults] -> Value
[InlineQueryResult] -> Encoding
[InlineQueryResult] -> Value
[InputInlineQueryResult] -> Encoding
[InputInlineQueryResult] -> Value
[HttpUrl] -> Encoding
[HttpUrl] -> Value
[ImportedContacts] -> Encoding
[ImportedContacts] -> Value
[Animations] -> Encoding
[Animations] -> Value
[PhoneNumberAuthenticationSettings] -> Encoding
[PhoneNumberAuthenticationSettings] -> Value
[Call] -> Encoding
[Call] -> Value
[CallProblem] -> Encoding
[CallProblem] -> Value
[CallState] -> Encoding
[CallState] -> Value
[CallId] -> Encoding
[CallId] -> Value
[CallConnection] -> Encoding
[CallConnection] -> Value
[CallProtocol] -> Encoding
[CallProtocol] -> Value
[CallDiscardReason] -> Encoding
[CallDiscardReason] -> Value
[StickerSets] -> Encoding
[StickerSets] -> Value
[StickerSetInfo] -> Encoding
[StickerSetInfo] -> Value
[StickerSet] -> Encoding
[StickerSet] -> Value
[Emojis] -> Encoding
[Emojis] -> Value
[Stickers] -> Encoding
[Stickers] -> Value
[UserStatus] -> Encoding
[UserStatus] -> Value
[ChatAction] -> Encoding
[ChatAction] -> Value
[SearchMessagesFilter] -> Encoding
[SearchMessagesFilter] -> Value
[InputMessageContent] -> Encoding
[InputMessageContent] -> Value
[SendMessageOptions] -> Encoding
[SendMessageOptions] -> Value
[MessageSchedulingState] -> Encoding
[MessageSchedulingState] -> Value
[InputThumbnail] -> Encoding
[InputThumbnail] -> Value
[TextEntityType] -> Encoding
[TextEntityType] -> Value
[MessageContent] -> Encoding
[MessageContent] -> Value
[InputPassportElementError] -> Encoding
[InputPassportElementError] -> Value
[InputPassportElementErrorSource] -> Encoding
[InputPassportElementErrorSource] -> Value
[EncryptedPassportElement] -> Encoding
[EncryptedPassportElement] -> Value
[EncryptedCredentials] -> Encoding
[EncryptedCredentials] -> Value
[PassportElementsWithErrors] -> Encoding
[PassportElementsWithErrors] -> Value
[PassportAuthorizationForm] -> Encoding
[PassportAuthorizationForm] -> Value
[PassportRequiredElement] -> Encoding
[PassportRequiredElement] -> Value
[PassportSuitableElement] -> Encoding
[PassportSuitableElement] -> Value
[PassportElementError] -> Encoding
[PassportElementError] -> Value
[PassportElementErrorSource] -> Encoding
[PassportElementErrorSource] -> Value
[PassportElements] -> Encoding
[PassportElements] -> Value
[InputPassportElement] -> Encoding
[InputPassportElement] -> Value
[PassportElement] -> Encoding
[PassportElement] -> Value
[InputPersonalDocument] -> Encoding
[InputPersonalDocument] -> Value
[PersonalDocument] -> Encoding
[PersonalDocument] -> Value
[InputIdentityDocument] -> Encoding
[InputIdentityDocument] -> Value
[IdentityDocument] -> Encoding
[IdentityDocument] -> Value
[PersonalDetails] -> Encoding
[PersonalDetails] -> Value
[Date] -> Encoding
[Date] -> Value
[PassportElementType] -> Encoding
[PassportElementType] -> Value
[DatedFile] -> Encoding
[DatedFile] -> Value
[PaymentReceipt] -> Encoding
[PaymentReceipt] -> Value
[PaymentResult] -> Encoding
[PaymentResult] -> Value
[ValidatedOrderInfo] -> Encoding
[ValidatedOrderInfo] -> Value
[PaymentForm] -> Encoding
[PaymentForm] -> Value
[PaymentsProviderStripe] -> Encoding
[PaymentsProviderStripe] -> Value
[InputCredentials] -> Encoding
[InputCredentials] -> Value
[SavedCredentials] -> Encoding
[SavedCredentials] -> Value
[ShippingOption] -> Encoding
[ShippingOption] -> Value
[OrderInfo] -> Encoding
[OrderInfo] -> Value
[Invoice] -> Encoding
[Invoice] -> Value
[LabeledPricePart] -> Encoding
[LabeledPricePart] -> Value
[Address] -> Encoding
[Address] -> Value
[BankCardInfo] -> Encoding
[BankCardInfo] -> Value
[BankCardActionOpenUrl] -> Encoding
[BankCardActionOpenUrl] -> Value
[WebPage] -> Encoding
[WebPage] -> Value
[WebPageInstantView] -> Encoding
[WebPageInstantView] -> Value
[PageBlock] -> Encoding
[PageBlock] -> Value
[PageBlockRelatedArticle] -> Encoding
[PageBlockRelatedArticle] -> Value
[PageBlockTableCell] -> Encoding
[PageBlockTableCell] -> Value
[PageBlockVerticalAlignment] -> Encoding
[PageBlockVerticalAlignment] -> Value
[PageBlockHorizontalAlignment] -> Encoding
[PageBlockHorizontalAlignment] -> Value
[PageBlockListItem] -> Encoding
[PageBlockListItem] -> Value
[PageBlockCaption] -> Encoding
[PageBlockCaption] -> Value
[RichText] -> Encoding
[RichText] -> Value
[LoginUrlInfo] -> Encoding
[LoginUrlInfo] -> Value
[ReplyMarkup] -> Encoding
[ReplyMarkup] -> Value
[InlineKeyboardButton] -> Encoding
[InlineKeyboardButton] -> Value
[InlineKeyboardButtonType] -> Encoding
[InlineKeyboardButtonType] -> Value
[KeyboardButton] -> Encoding
[KeyboardButton] -> Value
[KeyboardButtonType] -> Encoding
[KeyboardButtonType] -> Value
[ChatActionBar] -> Encoding
[ChatActionBar] -> Value
[PublicChatType] -> Encoding
[PublicChatType] -> Value
[ChatInviteLinkInfo] -> Encoding
[ChatInviteLinkInfo] -> Value
[ChatInviteLink] -> Encoding
[ChatInviteLink] -> Value
[ChatsNearby] -> Encoding
[ChatsNearby] -> Value
[ChatNearby] -> Encoding
[ChatNearby] -> Value
[Chats] -> Encoding
[Chats] -> Value
[Chat] -> Encoding
[Chat] -> Value
[ChatSource] -> Encoding
[ChatSource] -> Value
[ChatList] -> Encoding
[ChatList] -> Value
[ChatType] -> Encoding
[ChatType] -> Value
[DraftMessage] -> Encoding
[DraftMessage] -> Value
[ScopeNotificationSettings] -> Encoding
[ScopeNotificationSettings] -> Value
[ChatNotificationSettings] -> Encoding
[ChatNotificationSettings] -> Value
[NotificationSettingsScope] -> Encoding
[NotificationSettingsScope] -> Value
[FoundMessages] -> Encoding
[FoundMessages] -> Value
[Messages] -> Encoding
[Messages] -> Value
[Message] -> Encoding
[Message] -> Value
[MessageSendingState] -> Encoding
[MessageSendingState] -> Value
[MessageForwardInfo] -> Encoding
[MessageForwardInfo] -> Value
[MessageForwardOrigin] -> Encoding
[MessageForwardOrigin] -> Value
[SecretChat] -> Encoding
[SecretChat] -> Value
[SecretChatState] -> Encoding
[SecretChatState] -> Value
[SupergroupFullInfo] -> Encoding
[SupergroupFullInfo] -> Value
[Supergroup] -> Encoding
[Supergroup] -> Value
[BasicGroupFullInfo] -> Encoding
[BasicGroupFullInfo] -> Value
[BasicGroup] -> Encoding
[BasicGroup] -> Value
[SupergroupMembersFilter] -> Encoding
[SupergroupMembersFilter] -> Value
[ChatMembersFilter] -> Encoding
[ChatMembersFilter] -> Value
[ChatMembers] -> Encoding
[ChatMembers] -> Value
[ChatMember] -> Encoding
[ChatMember] -> Value
[ChatMemberStatus] -> Encoding
[ChatMemberStatus] -> Value
[ChatPermissions] -> Encoding
[ChatPermissions] -> Value
[ChatAdministrators] -> Encoding
[ChatAdministrators] -> Value
[ChatAdministrator] -> Encoding
[ChatAdministrator] -> Value
[Users] -> Encoding
[Users] -> Value
[UserProfilePhotos] -> Encoding
[UserProfilePhotos] -> Value
[UserProfilePhoto] -> Encoding
[UserProfilePhoto] -> Value
[UserFullInfo] -> Encoding
[UserFullInfo] -> Value
[User] -> Encoding
[User] -> Value
[ChatLocation] -> Encoding
[ChatLocation] -> Value
[BotInfo] -> Encoding
[BotInfo] -> Value
[BotCommand] -> Encoding
[BotCommand] -> Value
[UserType] -> Encoding
[UserType] -> Value
[ChatPhoto] -> Encoding
[ChatPhoto] -> Value
[ProfilePhoto] -> Encoding
[ProfilePhoto] -> Value
[Poll] -> Encoding
[Poll] -> Value
[Game] -> Encoding
[Game] -> Value
[Venue] -> Encoding
[Venue] -> Value
[Location] -> Encoding
[Location] -> Value
[Contact] -> Encoding
[Contact] -> Value
[VoiceNote] -> Encoding
[VoiceNote] -> Value
[VideoNote] -> Encoding
[VideoNote] -> Value
[Video] -> Encoding
[Video] -> Value
[Sticker] -> Encoding
[Sticker] -> Value
[Photo] -> Encoding
[Photo] -> Value
[Document] -> Encoding
[Document] -> Value
[Audio] -> Encoding
[Audio] -> Value
[Animation] -> Encoding
[Animation] -> Value
[PollType] -> Encoding
[PollType] -> Value
[PollOption] -> Encoding
[PollOption] -> Value
[MaskPosition] -> Encoding
[MaskPosition] -> Value
[MaskPoint] -> Encoding
[MaskPoint] -> Value
[Minithumbnail] -> Encoding
[Minithumbnail] -> Value
[PhotoSize] -> Encoding
[PhotoSize] -> Value
[InputFile] -> Encoding
[InputFile] -> Value
[File] -> Encoding
[File] -> Value
[RemoteFile] -> Encoding
[RemoteFile] -> Value
[LocalFile] -> Encoding
[LocalFile] -> Value
[TemporaryPasswordState] -> Encoding
[TemporaryPasswordState] -> Value
[RecoveryEmailAddress] -> Encoding
[RecoveryEmailAddress] -> Value
[PasswordState] -> Encoding
[PasswordState] -> Value
[AuthorizationState] -> Encoding
[AuthorizationState] -> Value
[TermsOfService] -> Encoding
[TermsOfService] -> Value
[FormattedText] -> Encoding
[FormattedText] -> Value
[TextEntities] -> Encoding
[TextEntities] -> Value
[TextEntity] -> Encoding
[TextEntity] -> Value
[EmailAddressAuthenticationCodeInfo] -> Encoding
[EmailAddressAuthenticationCodeInfo] -> Value
[AuthenticationCodeInfo] -> Encoding
[AuthenticationCodeInfo] -> Value
[AuthenticationCodeType] -> Encoding
[AuthenticationCodeType] -> Value
[TdlibParameters] -> Encoding
[TdlibParameters] -> Value
[Ok] -> Encoding
[Ok] -> Value
[Error] -> Encoding
[Error] -> Value
Value -> Parser [TestVectorStringObject]
Value -> Parser [TestVectorString]
Value -> Parser [TestVectorIntObject]
Value -> Parser [TestVectorInt]
Value -> Parser [TestBytes]
Value -> Parser [TestString]
Value -> Parser [TestInt]
Value -> Parser [LogTags]
Value -> Parser [LogVerbosityLevel]
Value -> Parser [LogStream]
Value -> Parser [Updates]
Value -> Parser [Update]
Value -> Parser [ChatStatistics]
Value -> Parser [ChatStatisticsMessageInteractionCounters]
Value -> Parser [StatisticsGraph]
Value -> Parser [StatisticsValue]
Value -> Parser [DateRange]
Value -> Parser [InputSticker]
Value -> Parser [Proxies]
Value -> Parser [Proxy]
Value -> Parser [ProxyType]
Value -> Parser [TextParseMode]
Value -> Parser [DeepLinkInfo]
Value -> Parser [Seconds]
Value -> Parser [Text]
Value -> Parser [Count]
Value -> Parser [TMeUrls]
Value -> Parser [TMeUrl]
Value -> Parser [TMeUrlType]
Value -> Parser [TopChatCategory]
Value -> Parser [ConnectionState]
Value -> Parser [AutoDownloadSettingsPresets]
Value -> Parser [AutoDownloadSettings]
Value -> Parser [NetworkStatistics]
Value -> Parser [NetworkStatisticsEntry]
Value -> Parser [NetworkType]
Value -> Parser [DatabaseStatistics]
Value -> Parser [StorageStatisticsFast]
Value -> Parser [StorageStatistics]
Value -> Parser [StorageStatisticsByChat]
Value -> Parser [StorageStatisticsByFileType]
Value -> Parser [FileType]
Value -> Parser [FilePart]
Value -> Parser [MessageLinkInfo]
Value -> Parser [PublicMessageLink]
Value -> Parser [ChatReportReason]
Value -> Parser [ConnectedWebsites]
Value -> Parser [ConnectedWebsite]
Value -> Parser [Sessions]
Value -> Parser [Session]
Value -> Parser [AccountTtl]
Value -> Parser [UserPrivacySetting]
Value -> Parser [UserPrivacySettingRules]
Value -> Parser [UserPrivacySettingRule]
Value -> Parser [JsonValue]
Value -> Parser [JsonObjectMember]
Value -> Parser [OptionValue]
Value -> Parser [NotificationGroup]
Value -> Parser [Notification]
Value -> Parser [NotificationGroupType]
Value -> Parser [NotificationType]
Value -> Parser [PushMessageContent]
Value -> Parser [CheckChatUsernameResult]
Value -> Parser [CanTransferOwnershipResult]
Value -> Parser [Hashtags]
Value -> Parser [InputBackground]
Value -> Parser [Backgrounds]
Value -> Parser [Background]
Value -> Parser [BackgroundType]
Value -> Parser [BackgroundFill]
Value -> Parser [PushReceiverId]
Value -> Parser [DeviceToken]
Value -> Parser [LocalizationTargetInfo]
Value -> Parser [LanguagePackInfo]
Value -> Parser [LanguagePackStrings]
Value -> Parser [LanguagePackString]
Value -> Parser [LanguagePackStringValue]
Value -> Parser [ChatEventLogFilters]
Value -> Parser [ChatEvents]
Value -> Parser [ChatEvent]
Value -> Parser [ChatEventAction]
Value -> Parser [GameHighScores]
Value -> Parser [GameHighScore]
Value -> Parser [CustomRequestResult]
Value -> Parser [CallbackQueryAnswer]
Value -> Parser [CallbackQueryPayload]
Value -> Parser [InlineQueryResults]
Value -> Parser [InlineQueryResult]
Value -> Parser [InputInlineQueryResult]
Value -> Parser [HttpUrl]
Value -> Parser [ImportedContacts]
Value -> Parser [Animations]
Value -> Parser [PhoneNumberAuthenticationSettings]
Value -> Parser [Call]
Value -> Parser [CallProblem]
Value -> Parser [CallState]
Value -> Parser [CallId]
Value -> Parser [CallConnection]
Value -> Parser [CallProtocol]
Value -> Parser [CallDiscardReason]
Value -> Parser [StickerSets]
Value -> Parser [StickerSetInfo]
Value -> Parser [StickerSet]
Value -> Parser [Emojis]
Value -> Parser [Stickers]
Value -> Parser [UserStatus]
Value -> Parser [ChatAction]
Value -> Parser [SearchMessagesFilter]
Value -> Parser [InputMessageContent]
Value -> Parser [SendMessageOptions]
Value -> Parser [MessageSchedulingState]
Value -> Parser [InputThumbnail]
Value -> Parser [TextEntityType]
Value -> Parser [MessageContent]
Value -> Parser [InputPassportElementError]
Value -> Parser [InputPassportElementErrorSource]
Value -> Parser [EncryptedPassportElement]
Value -> Parser [EncryptedCredentials]
Value -> Parser [PassportElementsWithErrors]
Value -> Parser [PassportAuthorizationForm]
Value -> Parser [PassportRequiredElement]
Value -> Parser [PassportSuitableElement]
Value -> Parser [PassportElementError]
Value -> Parser [PassportElementErrorSource]
Value -> Parser [PassportElements]
Value -> Parser [InputPassportElement]
Value -> Parser [PassportElement]
Value -> Parser [InputPersonalDocument]
Value -> Parser [PersonalDocument]
Value -> Parser [InputIdentityDocument]
Value -> Parser [IdentityDocument]
Value -> Parser [PersonalDetails]
Value -> Parser [Date]
Value -> Parser [PassportElementType]
Value -> Parser [DatedFile]
Value -> Parser [PaymentReceipt]
Value -> Parser [PaymentResult]
Value -> Parser [ValidatedOrderInfo]
Value -> Parser [PaymentForm]
Value -> Parser [PaymentsProviderStripe]
Value -> Parser [InputCredentials]
Value -> Parser [SavedCredentials]
Value -> Parser [ShippingOption]
Value -> Parser [OrderInfo]
Value -> Parser [Invoice]
Value -> Parser [LabeledPricePart]
Value -> Parser [Address]
Value -> Parser [BankCardInfo]
Value -> Parser [BankCardActionOpenUrl]
Value -> Parser [WebPage]
Value -> Parser [WebPageInstantView]
Value -> Parser [PageBlock]
Value -> Parser [PageBlockRelatedArticle]
Value -> Parser [PageBlockTableCell]
Value -> Parser [PageBlockVerticalAlignment]
Value -> Parser [PageBlockHorizontalAlignment]
Value -> Parser [PageBlockListItem]
Value -> Parser [PageBlockCaption]
Value -> Parser [RichText]
Value -> Parser [LoginUrlInfo]
Value -> Parser [ReplyMarkup]
Value -> Parser [InlineKeyboardButton]
Value -> Parser [InlineKeyboardButtonType]
Value -> Parser [KeyboardButton]
Value -> Parser [KeyboardButtonType]
Value -> Parser [ChatActionBar]
Value -> Parser [PublicChatType]
Value -> Parser [ChatInviteLinkInfo]
Value -> Parser [ChatInviteLink]
Value -> Parser [ChatsNearby]
Value -> Parser [ChatNearby]
Value -> Parser [Chats]
Value -> Parser [Chat]
Value -> Parser [ChatSource]
Value -> Parser [ChatList]
Value -> Parser [ChatType]
Value -> Parser [DraftMessage]
Value -> Parser [ScopeNotificationSettings]
Value -> Parser [ChatNotificationSettings]
Value -> Parser [NotificationSettingsScope]
Value -> Parser [FoundMessages]
Value -> Parser [Messages]
Value -> Parser [Message]
Value -> Parser [MessageSendingState]
Value -> Parser [MessageForwardInfo]
Value -> Parser [MessageForwardOrigin]
Value -> Parser [SecretChat]
Value -> Parser [SecretChatState]
Value -> Parser [SupergroupFullInfo]
Value -> Parser [Supergroup]
Value -> Parser [BasicGroupFullInfo]
Value -> Parser [BasicGroup]
Value -> Parser [SupergroupMembersFilter]
Value -> Parser [ChatMembersFilter]
Value -> Parser [ChatMembers]
Value -> Parser [ChatMember]
Value -> Parser [ChatMemberStatus]
Value -> Parser [ChatPermissions]
Value -> Parser [ChatAdministrators]
Value -> Parser [ChatAdministrator]
Value -> Parser [Users]
Value -> Parser [UserProfilePhotos]
Value -> Parser [UserProfilePhoto]
Value -> Parser [UserFullInfo]
Value -> Parser [User]
Value -> Parser [ChatLocation]
Value -> Parser [BotInfo]
Value -> Parser [BotCommand]
Value -> Parser [UserType]
Value -> Parser [ChatPhoto]
Value -> Parser [ProfilePhoto]
Value -> Parser [Poll]
Value -> Parser [Game]
Value -> Parser [Venue]
Value -> Parser [Location]
Value -> Parser [Contact]
Value -> Parser [VoiceNote]
Value -> Parser [VideoNote]
Value -> Parser [Video]
Value -> Parser [Sticker]
Value -> Parser [Photo]
Value -> Parser [Document]
Value -> Parser [Audio]
Value -> Parser [Animation]
Value -> Parser [PollType]
Value -> Parser [PollOption]
Value -> Parser [MaskPosition]
Value -> Parser [MaskPoint]
Value -> Parser [Minithumbnail]
Value -> Parser [PhotoSize]
Value -> Parser [InputFile]
Value -> Parser [File]
Value -> Parser [RemoteFile]
Value -> Parser [LocalFile]
Value -> Parser [TemporaryPasswordState]
Value -> Parser [RecoveryEmailAddress]
Value -> Parser [PasswordState]
Value -> Parser [AuthorizationState]
Value -> Parser [TermsOfService]
Value -> Parser [FormattedText]
Value -> Parser [TextEntities]
Value -> Parser [TextEntity]
Value -> Parser [EmailAddressAuthenticationCodeInfo]
Value -> Parser [AuthenticationCodeInfo]
Value -> Parser [AuthenticationCodeType]
Value -> Parser [TdlibParameters]
Value -> Parser [Ok]
Value -> Parser [Error]
Value -> Parser TestVectorStringObject
Value -> Parser TestVectorString
Value -> Parser TestVectorIntObject
Value -> Parser TestVectorInt
Value -> Parser TestBytes
Value -> Parser TestString
Value -> Parser TestInt
Value -> Parser LogTags
Value -> Parser LogVerbosityLevel
Value -> Parser LogStream
Value -> Parser Updates
Value -> Parser Update
Value -> Parser ChatStatistics
Value -> Parser ChatStatisticsMessageInteractionCounters
Value -> Parser StatisticsGraph
Value -> Parser StatisticsValue
Value -> Parser DateRange
Value -> Parser InputSticker
Value -> Parser Proxies
Value -> Parser Proxy
Value -> Parser ProxyType
Value -> Parser TextParseMode
Value -> Parser DeepLinkInfo
Value -> Parser Seconds
Value -> Parser Text
Value -> Parser Count
Value -> Parser TMeUrls
Value -> Parser TMeUrl
Value -> Parser TMeUrlType
Value -> Parser TopChatCategory
Value -> Parser ConnectionState
Value -> Parser AutoDownloadSettingsPresets
Value -> Parser AutoDownloadSettings
Value -> Parser NetworkStatistics
Value -> Parser NetworkStatisticsEntry
Value -> Parser NetworkType
Value -> Parser DatabaseStatistics
Value -> Parser StorageStatisticsFast
Value -> Parser StorageStatistics
Value -> Parser StorageStatisticsByChat
Value -> Parser StorageStatisticsByFileType
Value -> Parser FileType
Value -> Parser FilePart
Value -> Parser MessageLinkInfo
Value -> Parser PublicMessageLink
Value -> Parser ChatReportReason
Value -> Parser ConnectedWebsites
Value -> Parser ConnectedWebsite
Value -> Parser Sessions
Value -> Parser Session
Value -> Parser AccountTtl
Value -> Parser UserPrivacySetting
Value -> Parser UserPrivacySettingRules
Value -> Parser UserPrivacySettingRule
Value -> Parser JsonValue
Value -> Parser JsonObjectMember
Value -> Parser OptionValue
Value -> Parser NotificationGroup
Value -> Parser Notification
Value -> Parser NotificationGroupType
Value -> Parser NotificationType
Value -> Parser PushMessageContent
Value -> Parser CheckChatUsernameResult
Value -> Parser CanTransferOwnershipResult
Value -> Parser Hashtags
Value -> Parser InputBackground
Value -> Parser Backgrounds
Value -> Parser Background
Value -> Parser BackgroundType
Value -> Parser BackgroundFill
Value -> Parser PushReceiverId
Value -> Parser DeviceToken
Value -> Parser LocalizationTargetInfo
Value -> Parser LanguagePackInfo
Value -> Parser LanguagePackStrings
Value -> Parser LanguagePackString
Value -> Parser LanguagePackStringValue
Value -> Parser ChatEventLogFilters
Value -> Parser ChatEvents
Value -> Parser ChatEvent
Value -> Parser ChatEventAction
Value -> Parser GameHighScores
Value -> Parser GameHighScore
Value -> Parser CustomRequestResult
Value -> Parser CallbackQueryAnswer
Value -> Parser CallbackQueryPayload
Value -> Parser InlineQueryResults
Value -> Parser InlineQueryResult
Value -> Parser InputInlineQueryResult
Value -> Parser HttpUrl
Value -> Parser ImportedContacts
Value -> Parser Animations
Value -> Parser PhoneNumberAuthenticationSettings
Value -> Parser Call
Value -> Parser CallProblem
Value -> Parser CallState
Value -> Parser CallId
Value -> Parser CallConnection
Value -> Parser CallProtocol
Value -> Parser CallDiscardReason
Value -> Parser StickerSets
Value -> Parser StickerSetInfo
Value -> Parser StickerSet
Value -> Parser Emojis
Value -> Parser Stickers
Value -> Parser UserStatus
Value -> Parser ChatAction
Value -> Parser SearchMessagesFilter
Value -> Parser InputMessageContent
Value -> Parser SendMessageOptions
Value -> Parser MessageSchedulingState
Value -> Parser InputThumbnail
Value -> Parser TextEntityType
Value -> Parser MessageContent
Value -> Parser InputPassportElementError
Value -> Parser InputPassportElementErrorSource
Value -> Parser EncryptedPassportElement
Value -> Parser EncryptedCredentials
Value -> Parser PassportElementsWithErrors
Value -> Parser PassportAuthorizationForm
Value -> Parser PassportRequiredElement
Value -> Parser PassportSuitableElement
Value -> Parser PassportElementError
Value -> Parser PassportElementErrorSource
Value -> Parser PassportElements
Value -> Parser InputPassportElement
Value -> Parser PassportElement
Value -> Parser InputPersonalDocument
Value -> Parser PersonalDocument
Value -> Parser InputIdentityDocument
Value -> Parser IdentityDocument
Value -> Parser PersonalDetails
Value -> Parser Date
Value -> Parser PassportElementType
Value -> Parser DatedFile
Value -> Parser PaymentReceipt
Value -> Parser PaymentResult
Value -> Parser ValidatedOrderInfo
Value -> Parser PaymentForm
Value -> Parser PaymentsProviderStripe
Value -> Parser InputCredentials
Value -> Parser SavedCredentials
Value -> Parser ShippingOption
Value -> Parser OrderInfo
Value -> Parser Invoice
Value -> Parser LabeledPricePart
Value -> Parser Address
Value -> Parser BankCardInfo
Value -> Parser BankCardActionOpenUrl
Value -> Parser WebPage
Value -> Parser WebPageInstantView
Value -> Parser PageBlock
Value -> Parser PageBlockRelatedArticle
Value -> Parser PageBlockTableCell
Value -> Parser PageBlockVerticalAlignment
Value -> Parser PageBlockHorizontalAlignment
Value -> Parser PageBlockListItem
Value -> Parser PageBlockCaption
Value -> Parser RichText
Value -> Parser LoginUrlInfo
Value -> Parser ReplyMarkup
Value -> Parser InlineKeyboardButton
Value -> Parser InlineKeyboardButtonType
Value -> Parser KeyboardButton
Value -> Parser KeyboardButtonType
Value -> Parser ChatActionBar
Value -> Parser PublicChatType
Value -> Parser ChatInviteLinkInfo
Value -> Parser ChatInviteLink
Value -> Parser ChatsNearby
Value -> Parser ChatNearby
Value -> Parser Chats
Value -> Parser Chat
Value -> Parser ChatSource
Value -> Parser ChatList
Value -> Parser ChatType
Value -> Parser DraftMessage
Value -> Parser ScopeNotificationSettings
Value -> Parser ChatNotificationSettings
Value -> Parser NotificationSettingsScope
Value -> Parser FoundMessages
Value -> Parser Messages
Value -> Parser Message
Value -> Parser MessageSendingState
Value -> Parser MessageForwardInfo
Value -> Parser MessageForwardOrigin
Value -> Parser SecretChat
Value -> Parser SecretChatState
Value -> Parser SupergroupFullInfo
Value -> Parser Supergroup
Value -> Parser BasicGroupFullInfo
Value -> Parser BasicGroup
Value -> Parser SupergroupMembersFilter
Value -> Parser ChatMembersFilter
Value -> Parser ChatMembers
Value -> Parser ChatMember
Value -> Parser ChatMemberStatus
Value -> Parser ChatPermissions
Value -> Parser ChatAdministrators
Value -> Parser ChatAdministrator
Value -> Parser Users
Value -> Parser UserProfilePhotos
Value -> Parser UserProfilePhoto
Value -> Parser UserFullInfo
Value -> Parser User
Value -> Parser ChatLocation
Value -> Parser BotInfo
Value -> Parser BotCommand
Value -> Parser UserType
Value -> Parser ChatPhoto
Value -> Parser ProfilePhoto
Value -> Parser Poll
Value -> Parser Game
Value -> Parser Venue
Value -> Parser Location
Value -> Parser Contact
Value -> Parser VoiceNote
Value -> Parser VideoNote
Value -> Parser Video
Value -> Parser Sticker
Value -> Parser Photo
Value -> Parser Document
Value -> Parser Audio
Value -> Parser Animation
Value -> Parser PollType
Value -> Parser PollOption
Value -> Parser MaskPosition
Value -> Parser MaskPoint
Value -> Parser Minithumbnail
Value -> Parser PhotoSize
Value -> Parser InputFile
Value -> Parser File
Value -> Parser RemoteFile
Value -> Parser LocalFile
Value -> Parser TemporaryPasswordState
Value -> Parser RecoveryEmailAddress
Value -> Parser PasswordState
Value -> Parser AuthorizationState
Value -> Parser TermsOfService
Value -> Parser FormattedText
Value -> Parser TextEntities
Value -> Parser TextEntity
Value -> Parser EmailAddressAuthenticationCodeInfo
Value -> Parser AuthenticationCodeInfo
Value -> Parser AuthenticationCodeType
Value -> Parser TdlibParameters
Value -> Parser Ok
Value -> Parser Error
TestVectorStringObject -> Encoding
TestVectorStringObject -> Value
TestVectorString -> Encoding
TestVectorString -> Value
TestVectorIntObject -> Encoding
TestVectorIntObject -> Value
TestVectorInt -> Encoding
TestVectorInt -> Value
TestBytes -> Encoding
TestBytes -> Value
TestString -> Encoding
TestString -> Value
TestInt -> Encoding
TestInt -> Value
LogTags -> Encoding
LogTags -> Value
LogVerbosityLevel -> Encoding
LogVerbosityLevel -> Value
LogStream -> Encoding
LogStream -> Value
Updates -> Encoding
Updates -> Value
Update -> Encoding
Update -> Value
ChatStatistics -> Encoding
ChatStatistics -> Value
ChatStatisticsMessageInteractionCounters -> Encoding
ChatStatisticsMessageInteractionCounters -> Value
StatisticsGraph -> Encoding
StatisticsGraph -> Value
StatisticsValue -> Encoding
StatisticsValue -> Value
DateRange -> Encoding
DateRange -> Value
InputSticker -> Encoding
InputSticker -> Value
Proxies -> Encoding
Proxies -> Value
Proxy -> Encoding
Proxy -> Value
ProxyType -> Encoding
ProxyType -> Value
TextParseMode -> Encoding
TextParseMode -> Value
DeepLinkInfo -> Encoding
DeepLinkInfo -> Value
Seconds -> Encoding
Seconds -> Value
Text -> Encoding
Text -> Value
Count -> Encoding
Count -> Value
TMeUrls -> Encoding
TMeUrls -> Value
TMeUrl -> Encoding
TMeUrl -> Value
TMeUrlType -> Encoding
TMeUrlType -> Value
TopChatCategory -> Encoding
TopChatCategory -> Value
ConnectionState -> Encoding
ConnectionState -> Value
AutoDownloadSettingsPresets -> Encoding
AutoDownloadSettingsPresets -> Value
AutoDownloadSettings -> Encoding
AutoDownloadSettings -> Value
NetworkStatistics -> Encoding
NetworkStatistics -> Value
NetworkStatisticsEntry -> Encoding
NetworkStatisticsEntry -> Value
NetworkType -> Encoding
NetworkType -> Value
DatabaseStatistics -> Encoding
DatabaseStatistics -> Value
StorageStatisticsFast -> Encoding
StorageStatisticsFast -> Value
StorageStatistics -> Encoding
StorageStatistics -> Value
StorageStatisticsByChat -> Encoding
StorageStatisticsByChat -> Value
StorageStatisticsByFileType -> Encoding
StorageStatisticsByFileType -> Value
FileType -> Encoding
FileType -> Value
FilePart -> Encoding
FilePart -> Value
MessageLinkInfo -> Encoding
MessageLinkInfo -> Value
PublicMessageLink -> Encoding
PublicMessageLink -> Value
ChatReportReason -> Encoding
ChatReportReason -> Value
ConnectedWebsites -> Encoding
ConnectedWebsites -> Value
ConnectedWebsite -> Encoding
ConnectedWebsite -> Value
Sessions -> Encoding
Sessions -> Value
Session -> Encoding
Session -> Value
AccountTtl -> Encoding
AccountTtl -> Value
UserPrivacySetting -> Encoding
UserPrivacySetting -> Value
UserPrivacySettingRules -> Encoding
UserPrivacySettingRules -> Value
UserPrivacySettingRule -> Encoding
UserPrivacySettingRule -> Value
JsonValue -> Encoding
JsonValue -> Value
JsonObjectMember -> Encoding
JsonObjectMember -> Value
OptionValue -> Encoding
OptionValue -> Value
NotificationGroup -> Encoding
NotificationGroup -> Value
Notification -> Encoding
Notification -> Value
NotificationGroupType -> Encoding
NotificationGroupType -> Value
NotificationType -> Encoding
NotificationType -> Value
PushMessageContent -> Encoding
PushMessageContent -> Value
CheckChatUsernameResult -> Encoding
CheckChatUsernameResult -> Value
CanTransferOwnershipResult -> Encoding
CanTransferOwnershipResult -> Value
Hashtags -> Encoding
Hashtags -> Value
InputBackground -> Encoding
InputBackground -> Value
Backgrounds -> Encoding
Backgrounds -> Value
Background -> Encoding
Background -> Value
BackgroundType -> Encoding
BackgroundType -> Value
BackgroundFill -> Encoding
BackgroundFill -> Value
PushReceiverId -> Encoding
PushReceiverId -> Value
DeviceToken -> Encoding
DeviceToken -> Value
LocalizationTargetInfo -> Encoding
LocalizationTargetInfo -> Value
LanguagePackInfo -> Encoding
LanguagePackInfo -> Value
LanguagePackStrings -> Encoding
LanguagePackStrings -> Value
LanguagePackString -> Encoding
LanguagePackString -> Value
LanguagePackStringValue -> Encoding
LanguagePackStringValue -> Value
ChatEventLogFilters -> Encoding
ChatEventLogFilters -> Value
ChatEvents -> Encoding
ChatEvents -> Value
ChatEvent -> Encoding
ChatEvent -> Value
ChatEventAction -> Encoding
ChatEventAction -> Value
GameHighScores -> Encoding
GameHighScores -> Value
GameHighScore -> Encoding
GameHighScore -> Value
CustomRequestResult -> Encoding
CustomRequestResult -> Value
CallbackQueryAnswer -> Encoding
CallbackQueryAnswer -> Value
CallbackQueryPayload -> Encoding
CallbackQueryPayload -> Value
InlineQueryResults -> Encoding
InlineQueryResults -> Value
InlineQueryResult -> Encoding
InlineQueryResult -> Value
InputInlineQueryResult -> Encoding
InputInlineQueryResult -> Value
HttpUrl -> Encoding
HttpUrl -> Value
ImportedContacts -> Encoding
ImportedContacts -> Value
Animations -> Encoding
Animations -> Value
PhoneNumberAuthenticationSettings -> Encoding
PhoneNumberAuthenticationSettings -> Value
Call -> Encoding
Call -> Value
CallProblem -> Encoding
CallProblem -> Value
CallState -> Encoding
CallState -> Value
CallId -> Encoding
CallId -> Value
CallConnection -> Encoding
CallConnection -> Value
CallProtocol -> Encoding
CallProtocol -> Value
CallDiscardReason -> Encoding
CallDiscardReason -> Value
StickerSets -> Encoding
StickerSets -> Value
StickerSetInfo -> Encoding
StickerSetInfo -> Value
StickerSet -> Encoding
StickerSet -> Value
Emojis -> Encoding
Emojis -> Value
Stickers -> Encoding
Stickers -> Value
UserStatus -> Encoding
UserStatus -> Value
ChatAction -> Encoding
ChatAction -> Value
SearchMessagesFilter -> Encoding
SearchMessagesFilter -> Value
InputMessageContent -> Encoding
InputMessageContent -> Value
SendMessageOptions -> Encoding
SendMessageOptions -> Value
MessageSchedulingState -> Encoding
MessageSchedulingState -> Value
InputThumbnail -> Encoding
InputThumbnail -> Value
TextEntityType -> Encoding
TextEntityType -> Value
MessageContent -> Encoding
MessageContent -> Value
InputPassportElementError -> Encoding
InputPassportElementError -> Value
InputPassportElementErrorSource -> Encoding
InputPassportElementErrorSource -> Value
EncryptedPassportElement -> Encoding
EncryptedPassportElement -> Value
EncryptedCredentials -> Encoding
EncryptedCredentials -> Value
PassportElementsWithErrors -> Encoding
PassportElementsWithErrors -> Value
PassportAuthorizationForm -> Encoding
PassportAuthorizationForm -> Value
PassportRequiredElement -> Encoding
PassportRequiredElement -> Value
PassportSuitableElement -> Encoding
PassportSuitableElement -> Value
PassportElementError -> Encoding
PassportElementError -> Value
PassportElementErrorSource -> Encoding
PassportElementErrorSource -> Value
PassportElements -> Encoding
PassportElements -> Value
InputPassportElement -> Encoding
InputPassportElement -> Value
PassportElement -> Encoding
PassportElement -> Value
InputPersonalDocument -> Encoding
InputPersonalDocument -> Value
PersonalDocument -> Encoding
PersonalDocument -> Value
InputIdentityDocument -> Encoding
InputIdentityDocument -> Value
IdentityDocument -> Encoding
IdentityDocument -> Value
PersonalDetails -> Encoding
PersonalDetails -> Value
Date -> Encoding
Date -> Value
PassportElementType -> Encoding
PassportElementType -> Value
DatedFile -> Encoding
DatedFile -> Value
PaymentReceipt -> Encoding
PaymentReceipt -> Value
PaymentResult -> Encoding
PaymentResult -> Value
ValidatedOrderInfo -> Encoding
ValidatedOrderInfo -> Value
PaymentForm -> Encoding
PaymentForm -> Value
PaymentsProviderStripe -> Encoding
PaymentsProviderStripe -> Value
InputCredentials -> Encoding
InputCredentials -> Value
SavedCredentials -> Encoding
SavedCredentials -> Value
ShippingOption -> Encoding
ShippingOption -> Value
OrderInfo -> Encoding
OrderInfo -> Value
Invoice -> Encoding
Invoice -> Value
LabeledPricePart -> Encoding
LabeledPricePart -> Value
Address -> Encoding
Address -> Value
BankCardInfo -> Encoding
BankCardInfo -> Value
BankCardActionOpenUrl -> Encoding
BankCardActionOpenUrl -> Value
WebPage -> Encoding
WebPage -> Value
WebPageInstantView -> Encoding
WebPageInstantView -> Value
PageBlock -> Encoding
PageBlock -> Value
PageBlockRelatedArticle -> Encoding
PageBlockRelatedArticle -> Value
PageBlockTableCell -> Encoding
PageBlockTableCell -> Value
PageBlockVerticalAlignment -> Encoding
PageBlockVerticalAlignment -> Value
PageBlockHorizontalAlignment -> Encoding
PageBlockHorizontalAlignment -> Value
PageBlockListItem -> Encoding
PageBlockListItem -> Value
PageBlockCaption -> Encoding
PageBlockCaption -> Value
RichText -> Encoding
RichText -> Value
LoginUrlInfo -> Encoding
LoginUrlInfo -> Value
ReplyMarkup -> Encoding
ReplyMarkup -> Value
InlineKeyboardButton -> Encoding
InlineKeyboardButton -> Value
InlineKeyboardButtonType -> Encoding
InlineKeyboardButtonType -> Value
KeyboardButton -> Encoding
KeyboardButton -> Value
KeyboardButtonType -> Encoding
KeyboardButtonType -> Value
ChatActionBar -> Encoding
ChatActionBar -> Value
PublicChatType -> Encoding
PublicChatType -> Value
ChatInviteLinkInfo -> Encoding
ChatInviteLinkInfo -> Value
ChatInviteLink -> Encoding
ChatInviteLink -> Value
ChatsNearby -> Encoding
ChatsNearby -> Value
ChatNearby -> Encoding
ChatNearby -> Value
Chats -> Encoding
Chats -> Value
Chat -> Encoding
Chat -> Value
ChatSource -> Encoding
ChatSource -> Value
ChatList -> Encoding
ChatList -> Value
ChatType -> Encoding
ChatType -> Value
DraftMessage -> Encoding
DraftMessage -> Value
ScopeNotificationSettings -> Encoding
ScopeNotificationSettings -> Value
ChatNotificationSettings -> Encoding
ChatNotificationSettings -> Value
NotificationSettingsScope -> Encoding
NotificationSettingsScope -> Value
FoundMessages -> Encoding
FoundMessages -> Value
Messages -> Encoding
Messages -> Value
Message -> Encoding
Message -> Value
MessageSendingState -> Encoding
MessageSendingState -> Value
MessageForwardInfo -> Encoding
MessageForwardInfo -> Value
MessageForwardOrigin -> Encoding
MessageForwardOrigin -> Value
SecretChat -> Encoding
SecretChat -> Value
SecretChatState -> Encoding
SecretChatState -> Value
SupergroupFullInfo -> Encoding
SupergroupFullInfo -> Value
Supergroup -> Encoding
Supergroup -> Value
BasicGroupFullInfo -> Encoding
BasicGroupFullInfo -> Value
BasicGroup -> Encoding
BasicGroup -> Value
SupergroupMembersFilter -> Encoding
SupergroupMembersFilter -> Value
ChatMembersFilter -> Encoding
ChatMembersFilter -> Value
ChatMembers -> Encoding
ChatMembers -> Value
ChatMember -> Encoding
ChatMember -> Value
ChatMemberStatus -> Encoding
ChatMemberStatus -> Value
ChatPermissions -> Encoding
ChatPermissions -> Value
ChatAdministrators -> Encoding
ChatAdministrators -> Value
ChatAdministrator -> Encoding
ChatAdministrator -> Value
Users -> Encoding
Users -> Value
UserProfilePhotos -> Encoding
UserProfilePhotos -> Value
UserProfilePhoto -> Encoding
UserProfilePhoto -> Value
UserFullInfo -> Encoding
UserFullInfo -> Value
User -> Encoding
User -> Value
ChatLocation -> Encoding
ChatLocation -> Value
BotInfo -> Encoding
BotInfo -> Value
BotCommand -> Encoding
BotCommand -> Value
UserType -> Encoding
UserType -> Value
ChatPhoto -> Encoding
ChatPhoto -> Value
ProfilePhoto -> Encoding
ProfilePhoto -> Value
Poll -> Encoding
Poll -> Value
Game -> Encoding
Game -> Value
Venue -> Encoding
Venue -> Value
Location -> Encoding
Location -> Value
Contact -> Encoding
Contact -> Value
VoiceNote -> Encoding
VoiceNote -> Value
VideoNote -> Encoding
VideoNote -> Value
Video -> Encoding
Video -> Value
Sticker -> Encoding
Sticker -> Value
Photo -> Encoding
Photo -> Value
Document -> Encoding
Document -> Value
Audio -> Encoding
Audio -> Value
Animation -> Encoding
Animation -> Value
PollType -> Encoding
PollType -> Value
PollOption -> Encoding
PollOption -> Value
MaskPosition -> Encoding
MaskPosition -> Value
MaskPoint -> Encoding
MaskPoint -> Value
Minithumbnail -> Encoding
Minithumbnail -> Value
PhotoSize -> Encoding
PhotoSize -> Value
InputFile -> Encoding
InputFile -> Value
File -> Encoding
File -> Value
RemoteFile -> Encoding
RemoteFile -> Value
LocalFile -> Encoding
LocalFile -> Value
TemporaryPasswordState -> Encoding
TemporaryPasswordState -> Value
RecoveryEmailAddress -> Encoding
RecoveryEmailAddress -> Value
PasswordState -> Encoding
PasswordState -> Value
AuthorizationState -> Encoding
AuthorizationState -> Value
TermsOfService -> Encoding
TermsOfService -> Value
FormattedText -> Encoding
FormattedText -> Value
TextEntities -> Encoding
TextEntities -> Value
TextEntity -> Encoding
TextEntity -> Value
EmailAddressAuthenticationCodeInfo -> Encoding
EmailAddressAuthenticationCodeInfo -> Value
AuthenticationCodeInfo -> Encoding
AuthenticationCodeInfo -> Value
AuthenticationCodeType -> Encoding
AuthenticationCodeType -> Value
TdlibParameters -> Encoding
TdlibParameters -> Value
Ok -> Encoding
Ok -> Value
Error -> Encoding
Error -> Value
(Value -> Parser TestVectorStringObject)
-> (Value -> Parser [TestVectorStringObject])
-> FromJSON TestVectorStringObject
(Value -> Parser TestVectorString)
-> (Value -> Parser [TestVectorString])
-> FromJSON TestVectorString
(Value -> Parser TestVectorIntObject)
-> (Value -> Parser [TestVectorIntObject])
-> FromJSON TestVectorIntObject
(Value -> Parser TestVectorInt)
-> (Value -> Parser [TestVectorInt]) -> FromJSON TestVectorInt
(Value -> Parser TestBytes)
-> (Value -> Parser [TestBytes]) -> FromJSON TestBytes
(Value -> Parser TestString)
-> (Value -> Parser [TestString]) -> FromJSON TestString
(Value -> Parser TestInt)
-> (Value -> Parser [TestInt]) -> FromJSON TestInt
(Value -> Parser LogTags)
-> (Value -> Parser [LogTags]) -> FromJSON LogTags
(Value -> Parser LogVerbosityLevel)
-> (Value -> Parser [LogVerbosityLevel])
-> FromJSON LogVerbosityLevel
(Value -> Parser LogStream)
-> (Value -> Parser [LogStream]) -> FromJSON LogStream
(Value -> Parser Updates)
-> (Value -> Parser [Updates]) -> FromJSON Updates
(Value -> Parser Update)
-> (Value -> Parser [Update]) -> FromJSON Update
(Value -> Parser ChatStatistics)
-> (Value -> Parser [ChatStatistics]) -> FromJSON ChatStatistics
(Value -> Parser ChatStatisticsMessageInteractionCounters)
-> (Value -> Parser [ChatStatisticsMessageInteractionCounters])
-> FromJSON ChatStatisticsMessageInteractionCounters
(Value -> Parser StatisticsGraph)
-> (Value -> Parser [StatisticsGraph]) -> FromJSON StatisticsGraph
(Value -> Parser StatisticsValue)
-> (Value -> Parser [StatisticsValue]) -> FromJSON StatisticsValue
(Value -> Parser DateRange)
-> (Value -> Parser [DateRange]) -> FromJSON DateRange
(Value -> Parser InputSticker)
-> (Value -> Parser [InputSticker]) -> FromJSON InputSticker
(Value -> Parser Proxies)
-> (Value -> Parser [Proxies]) -> FromJSON Proxies
(Value -> Parser Proxy)
-> (Value -> Parser [Proxy]) -> FromJSON Proxy
(Value -> Parser ProxyType)
-> (Value -> Parser [ProxyType]) -> FromJSON ProxyType
(Value -> Parser TextParseMode)
-> (Value -> Parser [TextParseMode]) -> FromJSON TextParseMode
(Value -> Parser DeepLinkInfo)
-> (Value -> Parser [DeepLinkInfo]) -> FromJSON DeepLinkInfo
(Value -> Parser Seconds)
-> (Value -> Parser [Seconds]) -> FromJSON Seconds
(Value -> Parser Text) -> (Value -> Parser [Text]) -> FromJSON Text
(Value -> Parser Count)
-> (Value -> Parser [Count]) -> FromJSON Count
(Value -> Parser TMeUrls)
-> (Value -> Parser [TMeUrls]) -> FromJSON TMeUrls
(Value -> Parser TMeUrl)
-> (Value -> Parser [TMeUrl]) -> FromJSON TMeUrl
(Value -> Parser TMeUrlType)
-> (Value -> Parser [TMeUrlType]) -> FromJSON TMeUrlType
(Value -> Parser TopChatCategory)
-> (Value -> Parser [TopChatCategory]) -> FromJSON TopChatCategory
(Value -> Parser ConnectionState)
-> (Value -> Parser [ConnectionState]) -> FromJSON ConnectionState
(Value -> Parser AutoDownloadSettingsPresets)
-> (Value -> Parser [AutoDownloadSettingsPresets])
-> FromJSON AutoDownloadSettingsPresets
(Value -> Parser AutoDownloadSettings)
-> (Value -> Parser [AutoDownloadSettings])
-> FromJSON AutoDownloadSettings
(Value -> Parser NetworkStatistics)
-> (Value -> Parser [NetworkStatistics])
-> FromJSON NetworkStatistics
(Value -> Parser NetworkStatisticsEntry)
-> (Value -> Parser [NetworkStatisticsEntry])
-> FromJSON NetworkStatisticsEntry
(Value -> Parser NetworkType)
-> (Value -> Parser [NetworkType]) -> FromJSON NetworkType
(Value -> Parser DatabaseStatistics)
-> (Value -> Parser [DatabaseStatistics])
-> FromJSON DatabaseStatistics
(Value -> Parser StorageStatisticsFast)
-> (Value -> Parser [StorageStatisticsFast])
-> FromJSON StorageStatisticsFast
(Value -> Parser StorageStatistics)
-> (Value -> Parser [StorageStatistics])
-> FromJSON StorageStatistics
(Value -> Parser StorageStatisticsByChat)
-> (Value -> Parser [StorageStatisticsByChat])
-> FromJSON StorageStatisticsByChat
(Value -> Parser StorageStatisticsByFileType)
-> (Value -> Parser [StorageStatisticsByFileType])
-> FromJSON StorageStatisticsByFileType
(Value -> Parser FileType)
-> (Value -> Parser [FileType]) -> FromJSON FileType
(Value -> Parser FilePart)
-> (Value -> Parser [FilePart]) -> FromJSON FilePart
(Value -> Parser MessageLinkInfo)
-> (Value -> Parser [MessageLinkInfo]) -> FromJSON MessageLinkInfo
(Value -> Parser PublicMessageLink)
-> (Value -> Parser [PublicMessageLink])
-> FromJSON PublicMessageLink
(Value -> Parser ChatReportReason)
-> (Value -> Parser [ChatReportReason])
-> FromJSON ChatReportReason
(Value -> Parser ConnectedWebsites)
-> (Value -> Parser [ConnectedWebsites])
-> FromJSON ConnectedWebsites
(Value -> Parser ConnectedWebsite)
-> (Value -> Parser [ConnectedWebsite])
-> FromJSON ConnectedWebsite
(Value -> Parser Sessions)
-> (Value -> Parser [Sessions]) -> FromJSON Sessions
(Value -> Parser Session)
-> (Value -> Parser [Session]) -> FromJSON Session
(Value -> Parser AccountTtl)
-> (Value -> Parser [AccountTtl]) -> FromJSON AccountTtl
(Value -> Parser UserPrivacySetting)
-> (Value -> Parser [UserPrivacySetting])
-> FromJSON UserPrivacySetting
(Value -> Parser UserPrivacySettingRules)
-> (Value -> Parser [UserPrivacySettingRules])
-> FromJSON UserPrivacySettingRules
(Value -> Parser UserPrivacySettingRule)
-> (Value -> Parser [UserPrivacySettingRule])
-> FromJSON UserPrivacySettingRule
(Value -> Parser JsonValue)
-> (Value -> Parser [JsonValue]) -> FromJSON JsonValue
(Value -> Parser JsonObjectMember)
-> (Value -> Parser [JsonObjectMember])
-> FromJSON JsonObjectMember
(Value -> Parser OptionValue)
-> (Value -> Parser [OptionValue]) -> FromJSON OptionValue
(Value -> Parser NotificationGroup)
-> (Value -> Parser [NotificationGroup])
-> FromJSON NotificationGroup
(Value -> Parser Notification)
-> (Value -> Parser [Notification]) -> FromJSON Notification
(Value -> Parser NotificationGroupType)
-> (Value -> Parser [NotificationGroupType])
-> FromJSON NotificationGroupType
(Value -> Parser NotificationType)
-> (Value -> Parser [NotificationType])
-> FromJSON NotificationType
(Value -> Parser PushMessageContent)
-> (Value -> Parser [PushMessageContent])
-> FromJSON PushMessageContent
(Value -> Parser CheckChatUsernameResult)
-> (Value -> Parser [CheckChatUsernameResult])
-> FromJSON CheckChatUsernameResult
(Value -> Parser CanTransferOwnershipResult)
-> (Value -> Parser [CanTransferOwnershipResult])
-> FromJSON CanTransferOwnershipResult
(Value -> Parser Hashtags)
-> (Value -> Parser [Hashtags]) -> FromJSON Hashtags
(Value -> Parser InputBackground)
-> (Value -> Parser [InputBackground]) -> FromJSON InputBackground
(Value -> Parser Backgrounds)
-> (Value -> Parser [Backgrounds]) -> FromJSON Backgrounds
(Value -> Parser Background)
-> (Value -> Parser [Background]) -> FromJSON Background
(Value -> Parser BackgroundType)
-> (Value -> Parser [BackgroundType]) -> FromJSON BackgroundType
(Value -> Parser BackgroundFill)
-> (Value -> Parser [BackgroundFill]) -> FromJSON BackgroundFill
(Value -> Parser PushReceiverId)
-> (Value -> Parser [PushReceiverId]) -> FromJSON PushReceiverId
(Value -> Parser DeviceToken)
-> (Value -> Parser [DeviceToken]) -> FromJSON DeviceToken
(Value -> Parser LocalizationTargetInfo)
-> (Value -> Parser [LocalizationTargetInfo])
-> FromJSON LocalizationTargetInfo
(Value -> Parser LanguagePackInfo)
-> (Value -> Parser [LanguagePackInfo])
-> FromJSON LanguagePackInfo
(Value -> Parser LanguagePackStrings)
-> (Value -> Parser [LanguagePackStrings])
-> FromJSON LanguagePackStrings
(Value -> Parser LanguagePackString)
-> (Value -> Parser [LanguagePackString])
-> FromJSON LanguagePackString
(Value -> Parser LanguagePackStringValue)
-> (Value -> Parser [LanguagePackStringValue])
-> FromJSON LanguagePackStringValue
(Value -> Parser ChatEventLogFilters)
-> (Value -> Parser [ChatEventLogFilters])
-> FromJSON ChatEventLogFilters
(Value -> Parser ChatEvents)
-> (Value -> Parser [ChatEvents]) -> FromJSON ChatEvents
(Value -> Parser ChatEvent)
-> (Value -> Parser [ChatEvent]) -> FromJSON ChatEvent
(Value -> Parser ChatEventAction)
-> (Value -> Parser [ChatEventAction]) -> FromJSON ChatEventAction
(Value -> Parser GameHighScores)
-> (Value -> Parser [GameHighScores]) -> FromJSON GameHighScores
(Value -> Parser GameHighScore)
-> (Value -> Parser [GameHighScore]) -> FromJSON GameHighScore
(Value -> Parser CustomRequestResult)
-> (Value -> Parser [CustomRequestResult])
-> FromJSON CustomRequestResult
(Value -> Parser CallbackQueryAnswer)
-> (Value -> Parser [CallbackQueryAnswer])
-> FromJSON CallbackQueryAnswer
(Value -> Parser CallbackQueryPayload)
-> (Value -> Parser [CallbackQueryPayload])
-> FromJSON CallbackQueryPayload
(Value -> Parser InlineQueryResults)
-> (Value -> Parser [InlineQueryResults])
-> FromJSON InlineQueryResults
(Value -> Parser InlineQueryResult)
-> (Value -> Parser [InlineQueryResult])
-> FromJSON InlineQueryResult
(Value -> Parser InputInlineQueryResult)
-> (Value -> Parser [InputInlineQueryResult])
-> FromJSON InputInlineQueryResult
(Value -> Parser HttpUrl)
-> (Value -> Parser [HttpUrl]) -> FromJSON HttpUrl
(Value -> Parser ImportedContacts)
-> (Value -> Parser [ImportedContacts])
-> FromJSON ImportedContacts
(Value -> Parser Animations)
-> (Value -> Parser [Animations]) -> FromJSON Animations
(Value -> Parser PhoneNumberAuthenticationSettings)
-> (Value -> Parser [PhoneNumberAuthenticationSettings])
-> FromJSON PhoneNumberAuthenticationSettings
(Value -> Parser Call) -> (Value -> Parser [Call]) -> FromJSON Call
(Value -> Parser CallProblem)
-> (Value -> Parser [CallProblem]) -> FromJSON CallProblem
(Value -> Parser CallState)
-> (Value -> Parser [CallState]) -> FromJSON CallState
(Value -> Parser CallId)
-> (Value -> Parser [CallId]) -> FromJSON CallId
(Value -> Parser CallConnection)
-> (Value -> Parser [CallConnection]) -> FromJSON CallConnection
(Value -> Parser CallProtocol)
-> (Value -> Parser [CallProtocol]) -> FromJSON CallProtocol
(Value -> Parser CallDiscardReason)
-> (Value -> Parser [CallDiscardReason])
-> FromJSON CallDiscardReason
(Value -> Parser StickerSets)
-> (Value -> Parser [StickerSets]) -> FromJSON StickerSets
(Value -> Parser StickerSetInfo)
-> (Value -> Parser [StickerSetInfo]) -> FromJSON StickerSetInfo
(Value -> Parser StickerSet)
-> (Value -> Parser [StickerSet]) -> FromJSON StickerSet
(Value -> Parser Emojis)
-> (Value -> Parser [Emojis]) -> FromJSON Emojis
(Value -> Parser Stickers)
-> (Value -> Parser [Stickers]) -> FromJSON Stickers
(Value -> Parser UserStatus)
-> (Value -> Parser [UserStatus]) -> FromJSON UserStatus
(Value -> Parser ChatAction)
-> (Value -> Parser [ChatAction]) -> FromJSON ChatAction
(Value -> Parser SearchMessagesFilter)
-> (Value -> Parser [SearchMessagesFilter])
-> FromJSON SearchMessagesFilter
(Value -> Parser InputMessageContent)
-> (Value -> Parser [InputMessageContent])
-> FromJSON InputMessageContent
(Value -> Parser SendMessageOptions)
-> (Value -> Parser [SendMessageOptions])
-> FromJSON SendMessageOptions
(Value -> Parser MessageSchedulingState)
-> (Value -> Parser [MessageSchedulingState])
-> FromJSON MessageSchedulingState
(Value -> Parser InputThumbnail)
-> (Value -> Parser [InputThumbnail]) -> FromJSON InputThumbnail
(Value -> Parser TextEntityType)
-> (Value -> Parser [TextEntityType]) -> FromJSON TextEntityType
(Value -> Parser MessageContent)
-> (Value -> Parser [MessageContent]) -> FromJSON MessageContent
(Value -> Parser InputPassportElementError)
-> (Value -> Parser [InputPassportElementError])
-> FromJSON InputPassportElementError
(Value -> Parser InputPassportElementErrorSource)
-> (Value -> Parser [InputPassportElementErrorSource])
-> FromJSON InputPassportElementErrorSource
(Value -> Parser EncryptedPassportElement)
-> (Value -> Parser [EncryptedPassportElement])
-> FromJSON EncryptedPassportElement
(Value -> Parser EncryptedCredentials)
-> (Value -> Parser [EncryptedCredentials])
-> FromJSON EncryptedCredentials
(Value -> Parser PassportElementsWithErrors)
-> (Value -> Parser [PassportElementsWithErrors])
-> FromJSON PassportElementsWithErrors
(Value -> Parser PassportAuthorizationForm)
-> (Value -> Parser [PassportAuthorizationForm])
-> FromJSON PassportAuthorizationForm
(Value -> Parser PassportRequiredElement)
-> (Value -> Parser [PassportRequiredElement])
-> FromJSON PassportRequiredElement
(Value -> Parser PassportSuitableElement)
-> (Value -> Parser [PassportSuitableElement])
-> FromJSON PassportSuitableElement
(Value -> Parser PassportElementError)
-> (Value -> Parser [PassportElementError])
-> FromJSON PassportElementError
(Value -> Parser PassportElementErrorSource)
-> (Value -> Parser [PassportElementErrorSource])
-> FromJSON PassportElementErrorSource
(Value -> Parser PassportElements)
-> (Value -> Parser [PassportElements])
-> FromJSON PassportElements
(Value -> Parser InputPassportElement)
-> (Value -> Parser [InputPassportElement])
-> FromJSON InputPassportElement
(Value -> Parser PassportElement)
-> (Value -> Parser [PassportElement]) -> FromJSON PassportElement
(Value -> Parser InputPersonalDocument)
-> (Value -> Parser [InputPersonalDocument])
-> FromJSON InputPersonalDocument
(Value -> Parser PersonalDocument)
-> (Value -> Parser [PersonalDocument])
-> FromJSON PersonalDocument
(Value -> Parser InputIdentityDocument)
-> (Value -> Parser [InputIdentityDocument])
-> FromJSON InputIdentityDocument
(Value -> Parser IdentityDocument)
-> (Value -> Parser [IdentityDocument])
-> FromJSON IdentityDocument
(Value -> Parser PersonalDetails)
-> (Value -> Parser [PersonalDetails]) -> FromJSON PersonalDetails
(Value -> Parser Date) -> (Value -> Parser [Date]) -> FromJSON Date
(Value -> Parser PassportElementType)
-> (Value -> Parser [PassportElementType])
-> FromJSON PassportElementType
(Value -> Parser DatedFile)
-> (Value -> Parser [DatedFile]) -> FromJSON DatedFile
(Value -> Parser PaymentReceipt)
-> (Value -> Parser [PaymentReceipt]) -> FromJSON PaymentReceipt
(Value -> Parser PaymentResult)
-> (Value -> Parser [PaymentResult]) -> FromJSON PaymentResult
(Value -> Parser ValidatedOrderInfo)
-> (Value -> Parser [ValidatedOrderInfo])
-> FromJSON ValidatedOrderInfo
(Value -> Parser PaymentForm)
-> (Value -> Parser [PaymentForm]) -> FromJSON PaymentForm
(Value -> Parser PaymentsProviderStripe)
-> (Value -> Parser [PaymentsProviderStripe])
-> FromJSON PaymentsProviderStripe
(Value -> Parser InputCredentials)
-> (Value -> Parser [InputCredentials])
-> FromJSON InputCredentials
(Value -> Parser SavedCredentials)
-> (Value -> Parser [SavedCredentials])
-> FromJSON SavedCredentials
(Value -> Parser ShippingOption)
-> (Value -> Parser [ShippingOption]) -> FromJSON ShippingOption
(Value -> Parser OrderInfo)
-> (Value -> Parser [OrderInfo]) -> FromJSON OrderInfo
(Value -> Parser Invoice)
-> (Value -> Parser [Invoice]) -> FromJSON Invoice
(Value -> Parser LabeledPricePart)
-> (Value -> Parser [LabeledPricePart])
-> FromJSON LabeledPricePart
(Value -> Parser Address)
-> (Value -> Parser [Address]) -> FromJSON Address
(Value -> Parser BankCardInfo)
-> (Value -> Parser [BankCardInfo]) -> FromJSON BankCardInfo
(Value -> Parser BankCardActionOpenUrl)
-> (Value -> Parser [BankCardActionOpenUrl])
-> FromJSON BankCardActionOpenUrl
(Value -> Parser WebPage)
-> (Value -> Parser [WebPage]) -> FromJSON WebPage
(Value -> Parser WebPageInstantView)
-> (Value -> Parser [WebPageInstantView])
-> FromJSON WebPageInstantView
(Value -> Parser PageBlock)
-> (Value -> Parser [PageBlock]) -> FromJSON PageBlock
(Value -> Parser PageBlockRelatedArticle)
-> (Value -> Parser [PageBlockRelatedArticle])
-> FromJSON PageBlockRelatedArticle
(Value -> Parser PageBlockTableCell)
-> (Value -> Parser [PageBlockTableCell])
-> FromJSON PageBlockTableCell
(Value -> Parser PageBlockVerticalAlignment)
-> (Value -> Parser [PageBlockVerticalAlignment])
-> FromJSON PageBlockVerticalAlignment
(Value -> Parser PageBlockHorizontalAlignment)
-> (Value -> Parser [PageBlockHorizontalAlignment])
-> FromJSON PageBlockHorizontalAlignment
(Value -> Parser PageBlockListItem)
-> (Value -> Parser [PageBlockListItem])
-> FromJSON PageBlockListItem
(Value -> Parser PageBlockCaption)
-> (Value -> Parser [PageBlockCaption])
-> FromJSON PageBlockCaption
(Value -> Parser RichText)
-> (Value -> Parser [RichText]) -> FromJSON RichText
(Value -> Parser LoginUrlInfo)
-> (Value -> Parser [LoginUrlInfo]) -> FromJSON LoginUrlInfo
(Value -> Parser ReplyMarkup)
-> (Value -> Parser [ReplyMarkup]) -> FromJSON ReplyMarkup
(Value -> Parser InlineKeyboardButton)
-> (Value -> Parser [InlineKeyboardButton])
-> FromJSON InlineKeyboardButton
(Value -> Parser InlineKeyboardButtonType)
-> (Value -> Parser [InlineKeyboardButtonType])
-> FromJSON InlineKeyboardButtonType
(Value -> Parser KeyboardButton)
-> (Value -> Parser [KeyboardButton]) -> FromJSON KeyboardButton
(Value -> Parser KeyboardButtonType)
-> (Value -> Parser [KeyboardButtonType])
-> FromJSON KeyboardButtonType
(Value -> Parser ChatActionBar)
-> (Value -> Parser [ChatActionBar]) -> FromJSON ChatActionBar
(Value -> Parser PublicChatType)
-> (Value -> Parser [PublicChatType]) -> FromJSON PublicChatType
(Value -> Parser ChatInviteLinkInfo)
-> (Value -> Parser [ChatInviteLinkInfo])
-> FromJSON ChatInviteLinkInfo
(Value -> Parser ChatInviteLink)
-> (Value -> Parser [ChatInviteLink]) -> FromJSON ChatInviteLink
(Value -> Parser ChatsNearby)
-> (Value -> Parser [ChatsNearby]) -> FromJSON ChatsNearby
(Value -> Parser ChatNearby)
-> (Value -> Parser [ChatNearby]) -> FromJSON ChatNearby
(Value -> Parser Chats)
-> (Value -> Parser [Chats]) -> FromJSON Chats
(Value -> Parser Chat) -> (Value -> Parser [Chat]) -> FromJSON Chat
(Value -> Parser ChatSource)
-> (Value -> Parser [ChatSource]) -> FromJSON ChatSource
(Value -> Parser ChatList)
-> (Value -> Parser [ChatList]) -> FromJSON ChatList
(Value -> Parser ChatType)
-> (Value -> Parser [ChatType]) -> FromJSON ChatType
(Value -> Parser DraftMessage)
-> (Value -> Parser [DraftMessage]) -> FromJSON DraftMessage
(Value -> Parser ScopeNotificationSettings)
-> (Value -> Parser [ScopeNotificationSettings])
-> FromJSON ScopeNotificationSettings
(Value -> Parser ChatNotificationSettings)
-> (Value -> Parser [ChatNotificationSettings])
-> FromJSON ChatNotificationSettings
(Value -> Parser NotificationSettingsScope)
-> (Value -> Parser [NotificationSettingsScope])
-> FromJSON NotificationSettingsScope
(Value -> Parser FoundMessages)
-> (Value -> Parser [FoundMessages]) -> FromJSON FoundMessages
(Value -> Parser Messages)
-> (Value -> Parser [Messages]) -> FromJSON Messages
(Value -> Parser Message)
-> (Value -> Parser [Message]) -> FromJSON Message
(Value -> Parser MessageSendingState)
-> (Value -> Parser [MessageSendingState])
-> FromJSON MessageSendingState
(Value -> Parser MessageForwardInfo)
-> (Value -> Parser [MessageForwardInfo])
-> FromJSON MessageForwardInfo
(Value -> Parser MessageForwardOrigin)
-> (Value -> Parser [MessageForwardOrigin])
-> FromJSON MessageForwardOrigin
(Value -> Parser SecretChat)
-> (Value -> Parser [SecretChat]) -> FromJSON SecretChat
(Value -> Parser SecretChatState)
-> (Value -> Parser [SecretChatState]) -> FromJSON SecretChatState
(Value -> Parser SupergroupFullInfo)
-> (Value -> Parser [SupergroupFullInfo])
-> FromJSON SupergroupFullInfo
(Value -> Parser Supergroup)
-> (Value -> Parser [Supergroup]) -> FromJSON Supergroup
(Value -> Parser BasicGroupFullInfo)
-> (Value -> Parser [BasicGroupFullInfo])
-> FromJSON BasicGroupFullInfo
(Value -> Parser BasicGroup)
-> (Value -> Parser [BasicGroup]) -> FromJSON BasicGroup
(Value -> Parser SupergroupMembersFilter)
-> (Value -> Parser [SupergroupMembersFilter])
-> FromJSON SupergroupMembersFilter
(Value -> Parser ChatMembersFilter)
-> (Value -> Parser [ChatMembersFilter])
-> FromJSON ChatMembersFilter
(Value -> Parser ChatMembers)
-> (Value -> Parser [ChatMembers]) -> FromJSON ChatMembers
(Value -> Parser ChatMember)
-> (Value -> Parser [ChatMember]) -> FromJSON ChatMember
(Value -> Parser ChatMemberStatus)
-> (Value -> Parser [ChatMemberStatus])
-> FromJSON ChatMemberStatus
(Value -> Parser ChatPermissions)
-> (Value -> Parser [ChatPermissions]) -> FromJSON ChatPermissions
(Value -> Parser ChatAdministrators)
-> (Value -> Parser [ChatAdministrators])
-> FromJSON ChatAdministrators
(Value -> Parser ChatAdministrator)
-> (Value -> Parser [ChatAdministrator])
-> FromJSON ChatAdministrator
(Value -> Parser Users)
-> (Value -> Parser [Users]) -> FromJSON Users
(Value -> Parser UserProfilePhotos)
-> (Value -> Parser [UserProfilePhotos])
-> FromJSON UserProfilePhotos
(Value -> Parser UserProfilePhoto)
-> (Value -> Parser [UserProfilePhoto])
-> FromJSON UserProfilePhoto
(Value -> Parser UserFullInfo)
-> (Value -> Parser [UserFullInfo]) -> FromJSON UserFullInfo
(Value -> Parser User) -> (Value -> Parser [User]) -> FromJSON User
(Value -> Parser ChatLocation)
-> (Value -> Parser [ChatLocation]) -> FromJSON ChatLocation
(Value -> Parser BotInfo)
-> (Value -> Parser [BotInfo]) -> FromJSON BotInfo
(Value -> Parser BotCommand)
-> (Value -> Parser [BotCommand]) -> FromJSON BotCommand
(Value -> Parser UserType)
-> (Value -> Parser [UserType]) -> FromJSON UserType
(Value -> Parser ChatPhoto)
-> (Value -> Parser [ChatPhoto]) -> FromJSON ChatPhoto
(Value -> Parser ProfilePhoto)
-> (Value -> Parser [ProfilePhoto]) -> FromJSON ProfilePhoto
(Value -> Parser Poll) -> (Value -> Parser [Poll]) -> FromJSON Poll
(Value -> Parser Game) -> (Value -> Parser [Game]) -> FromJSON Game
(Value -> Parser Venue)
-> (Value -> Parser [Venue]) -> FromJSON Venue
(Value -> Parser Location)
-> (Value -> Parser [Location]) -> FromJSON Location
(Value -> Parser Contact)
-> (Value -> Parser [Contact]) -> FromJSON Contact
(Value -> Parser VoiceNote)
-> (Value -> Parser [VoiceNote]) -> FromJSON VoiceNote
(Value -> Parser VideoNote)
-> (Value -> Parser [VideoNote]) -> FromJSON VideoNote
(Value -> Parser Video)
-> (Value -> Parser [Video]) -> FromJSON Video
(Value -> Parser Sticker)
-> (Value -> Parser [Sticker]) -> FromJSON Sticker
(Value -> Parser Photo)
-> (Value -> Parser [Photo]) -> FromJSON Photo
(Value -> Parser Document)
-> (Value -> Parser [Document]) -> FromJSON Document
(Value -> Parser Audio)
-> (Value -> Parser [Audio]) -> FromJSON Audio
(Value -> Parser Animation)
-> (Value -> Parser [Animation]) -> FromJSON Animation
(Value -> Parser PollType)
-> (Value -> Parser [PollType]) -> FromJSON PollType
(Value -> Parser PollOption)
-> (Value -> Parser [PollOption]) -> FromJSON PollOption
(Value -> Parser MaskPosition)
-> (Value -> Parser [MaskPosition]) -> FromJSON MaskPosition
(Value -> Parser MaskPoint)
-> (Value -> Parser [MaskPoint]) -> FromJSON MaskPoint
(Value -> Parser Minithumbnail)
-> (Value -> Parser [Minithumbnail]) -> FromJSON Minithumbnail
(Value -> Parser PhotoSize)
-> (Value -> Parser [PhotoSize]) -> FromJSON PhotoSize
(Value -> Parser InputFile)
-> (Value -> Parser [InputFile]) -> FromJSON InputFile
(Value -> Parser File) -> (Value -> Parser [File]) -> FromJSON File
(Value -> Parser RemoteFile)
-> (Value -> Parser [RemoteFile]) -> FromJSON RemoteFile
(Value -> Parser LocalFile)
-> (Value -> Parser [LocalFile]) -> FromJSON LocalFile
(Value -> Parser TemporaryPasswordState)
-> (Value -> Parser [TemporaryPasswordState])
-> FromJSON TemporaryPasswordState
(Value -> Parser RecoveryEmailAddress)
-> (Value -> Parser [RecoveryEmailAddress])
-> FromJSON RecoveryEmailAddress
(Value -> Parser PasswordState)
-> (Value -> Parser [PasswordState]) -> FromJSON PasswordState
(Value -> Parser AuthorizationState)
-> (Value -> Parser [AuthorizationState])
-> FromJSON AuthorizationState
(Value -> Parser TermsOfService)
-> (Value -> Parser [TermsOfService]) -> FromJSON TermsOfService
(Value -> Parser FormattedText)
-> (Value -> Parser [FormattedText]) -> FromJSON FormattedText
(Value -> Parser TextEntities)
-> (Value -> Parser [TextEntities]) -> FromJSON TextEntities
(Value -> Parser TextEntity)
-> (Value -> Parser [TextEntity]) -> FromJSON TextEntity
(Value -> Parser EmailAddressAuthenticationCodeInfo)
-> (Value -> Parser [EmailAddressAuthenticationCodeInfo])
-> FromJSON EmailAddressAuthenticationCodeInfo
(Value -> Parser AuthenticationCodeInfo)
-> (Value -> Parser [AuthenticationCodeInfo])
-> FromJSON AuthenticationCodeInfo
(Value -> Parser AuthenticationCodeType)
-> (Value -> Parser [AuthenticationCodeType])
-> FromJSON AuthenticationCodeType
(Value -> Parser TdlibParameters)
-> (Value -> Parser [TdlibParameters]) -> FromJSON TdlibParameters
(Value -> Parser Ok) -> (Value -> Parser [Ok]) -> FromJSON Ok
(Value -> Parser Error)
-> (Value -> Parser [Error]) -> FromJSON Error
(TestVectorStringObject -> Value)
-> (TestVectorStringObject -> Encoding)
-> ([TestVectorStringObject] -> Value)
-> ([TestVectorStringObject] -> Encoding)
-> ToJSON TestVectorStringObject
(TestVectorString -> Value)
-> (TestVectorString -> Encoding)
-> ([TestVectorString] -> Value)
-> ([TestVectorString] -> Encoding)
-> ToJSON TestVectorString
(TestVectorIntObject -> Value)
-> (TestVectorIntObject -> Encoding)
-> ([TestVectorIntObject] -> Value)
-> ([TestVectorIntObject] -> Encoding)
-> ToJSON TestVectorIntObject
(TestVectorInt -> Value)
-> (TestVectorInt -> Encoding)
-> ([TestVectorInt] -> Value)
-> ([TestVectorInt] -> Encoding)
-> ToJSON TestVectorInt
(TestBytes -> Value)
-> (TestBytes -> Encoding)
-> ([TestBytes] -> Value)
-> ([TestBytes] -> Encoding)
-> ToJSON TestBytes
(TestString -> Value)
-> (TestString -> Encoding)
-> ([TestString] -> Value)
-> ([TestString] -> Encoding)
-> ToJSON TestString
(TestInt -> Value)
-> (TestInt -> Encoding)
-> ([TestInt] -> Value)
-> ([TestInt] -> Encoding)
-> ToJSON TestInt
(LogTags -> Value)
-> (LogTags -> Encoding)
-> ([LogTags] -> Value)
-> ([LogTags] -> Encoding)
-> ToJSON LogTags
(LogVerbosityLevel -> Value)
-> (LogVerbosityLevel -> Encoding)
-> ([LogVerbosityLevel] -> Value)
-> ([LogVerbosityLevel] -> Encoding)
-> ToJSON LogVerbosityLevel
(LogStream -> Value)
-> (LogStream -> Encoding)
-> ([LogStream] -> Value)
-> ([LogStream] -> Encoding)
-> ToJSON LogStream
(Updates -> Value)
-> (Updates -> Encoding)
-> ([Updates] -> Value)
-> ([Updates] -> Encoding)
-> ToJSON Updates
(Update -> Value)
-> (Update -> Encoding)
-> ([Update] -> Value)
-> ([Update] -> Encoding)
-> ToJSON Update
(ChatStatistics -> Value)
-> (ChatStatistics -> Encoding)
-> ([ChatStatistics] -> Value)
-> ([ChatStatistics] -> Encoding)
-> ToJSON ChatStatistics
(ChatStatisticsMessageInteractionCounters -> Value)
-> (ChatStatisticsMessageInteractionCounters -> Encoding)
-> ([ChatStatisticsMessageInteractionCounters] -> Value)
-> ([ChatStatisticsMessageInteractionCounters] -> Encoding)
-> ToJSON ChatStatisticsMessageInteractionCounters
(StatisticsGraph -> Value)
-> (StatisticsGraph -> Encoding)
-> ([StatisticsGraph] -> Value)
-> ([StatisticsGraph] -> Encoding)
-> ToJSON StatisticsGraph
(StatisticsValue -> Value)
-> (StatisticsValue -> Encoding)
-> ([StatisticsValue] -> Value)
-> ([StatisticsValue] -> Encoding)
-> ToJSON StatisticsValue
(DateRange -> Value)
-> (DateRange -> Encoding)
-> ([DateRange] -> Value)
-> ([DateRange] -> Encoding)
-> ToJSON DateRange
(InputSticker -> Value)
-> (InputSticker -> Encoding)
-> ([InputSticker] -> Value)
-> ([InputSticker] -> Encoding)
-> ToJSON InputSticker
(Proxies -> Value)
-> (Proxies -> Encoding)
-> ([Proxies] -> Value)
-> ([Proxies] -> Encoding)
-> ToJSON Proxies
(Proxy -> Value)
-> (Proxy -> Encoding)
-> ([Proxy] -> Value)
-> ([Proxy] -> Encoding)
-> ToJSON Proxy
(ProxyType -> Value)
-> (ProxyType -> Encoding)
-> ([ProxyType] -> Value)
-> ([ProxyType] -> Encoding)
-> ToJSON ProxyType
(TextParseMode -> Value)
-> (TextParseMode -> Encoding)
-> ([TextParseMode] -> Value)
-> ([TextParseMode] -> Encoding)
-> ToJSON TextParseMode
(DeepLinkInfo -> Value)
-> (DeepLinkInfo -> Encoding)
-> ([DeepLinkInfo] -> Value)
-> ([DeepLinkInfo] -> Encoding)
-> ToJSON DeepLinkInfo
(Seconds -> Value)
-> (Seconds -> Encoding)
-> ([Seconds] -> Value)
-> ([Seconds] -> Encoding)
-> ToJSON Seconds
(Text -> Value)
-> (Text -> Encoding)
-> ([Text] -> Value)
-> ([Text] -> Encoding)
-> ToJSON Text
(Count -> Value)
-> (Count -> Encoding)
-> ([Count] -> Value)
-> ([Count] -> Encoding)
-> ToJSON Count
(TMeUrls -> Value)
-> (TMeUrls -> Encoding)
-> ([TMeUrls] -> Value)
-> ([TMeUrls] -> Encoding)
-> ToJSON TMeUrls
(TMeUrl -> Value)
-> (TMeUrl -> Encoding)
-> ([TMeUrl] -> Value)
-> ([TMeUrl] -> Encoding)
-> ToJSON TMeUrl
(TMeUrlType -> Value)
-> (TMeUrlType -> Encoding)
-> ([TMeUrlType] -> Value)
-> ([TMeUrlType] -> Encoding)
-> ToJSON TMeUrlType
(TopChatCategory -> Value)
-> (TopChatCategory -> Encoding)
-> ([TopChatCategory] -> Value)
-> ([TopChatCategory] -> Encoding)
-> ToJSON TopChatCategory
(ConnectionState -> Value)
-> (ConnectionState -> Encoding)
-> ([ConnectionState] -> Value)
-> ([ConnectionState] -> Encoding)
-> ToJSON ConnectionState
(AutoDownloadSettingsPresets -> Value)
-> (AutoDownloadSettingsPresets -> Encoding)
-> ([AutoDownloadSettingsPresets] -> Value)
-> ([AutoDownloadSettingsPresets] -> Encoding)
-> ToJSON AutoDownloadSettingsPresets
(AutoDownloadSettings -> Value)
-> (AutoDownloadSettings -> Encoding)
-> ([AutoDownloadSettings] -> Value)
-> ([AutoDownloadSettings] -> Encoding)
-> ToJSON AutoDownloadSettings
(NetworkStatistics -> Value)
-> (NetworkStatistics -> Encoding)
-> ([NetworkStatistics] -> Value)
-> ([NetworkStatistics] -> Encoding)
-> ToJSON NetworkStatistics
(NetworkStatisticsEntry -> Value)
-> (NetworkStatisticsEntry -> Encoding)
-> ([NetworkStatisticsEntry] -> Value)
-> ([NetworkStatisticsEntry] -> Encoding)
-> ToJSON NetworkStatisticsEntry
(NetworkType -> Value)
-> (NetworkType -> Encoding)
-> ([NetworkType] -> Value)
-> ([NetworkType] -> Encoding)
-> ToJSON NetworkType
(DatabaseStatistics -> Value)
-> (DatabaseStatistics -> Encoding)
-> ([DatabaseStatistics] -> Value)
-> ([DatabaseStatistics] -> Encoding)
-> ToJSON DatabaseStatistics
(StorageStatisticsFast -> Value)
-> (StorageStatisticsFast -> Encoding)
-> ([StorageStatisticsFast] -> Value)
-> ([StorageStatisticsFast] -> Encoding)
-> ToJSON StorageStatisticsFast
(StorageStatistics -> Value)
-> (StorageStatistics -> Encoding)
-> ([StorageStatistics] -> Value)
-> ([StorageStatistics] -> Encoding)
-> ToJSON StorageStatistics
(StorageStatisticsByChat -> Value)
-> (StorageStatisticsByChat -> Encoding)
-> ([StorageStatisticsByChat] -> Value)
-> ([StorageStatisticsByChat] -> Encoding)
-> ToJSON StorageStatisticsByChat
(StorageStatisticsByFileType -> Value)
-> (StorageStatisticsByFileType -> Encoding)
-> ([StorageStatisticsByFileType] -> Value)
-> ([StorageStatisticsByFileType] -> Encoding)
-> ToJSON StorageStatisticsByFileType
(FileType -> Value)
-> (FileType -> Encoding)
-> ([FileType] -> Value)
-> ([FileType] -> Encoding)
-> ToJSON FileType
(FilePart -> Value)
-> (FilePart -> Encoding)
-> ([FilePart] -> Value)
-> ([FilePart] -> Encoding)
-> ToJSON FilePart
(MessageLinkInfo -> Value)
-> (MessageLinkInfo -> Encoding)
-> ([MessageLinkInfo] -> Value)
-> ([MessageLinkInfo] -> Encoding)
-> ToJSON MessageLinkInfo
(PublicMessageLink -> Value)
-> (PublicMessageLink -> Encoding)
-> ([PublicMessageLink] -> Value)
-> ([PublicMessageLink] -> Encoding)
-> ToJSON PublicMessageLink
(ChatReportReason -> Value)
-> (ChatReportReason -> Encoding)
-> ([ChatReportReason] -> Value)
-> ([ChatReportReason] -> Encoding)
-> ToJSON ChatReportReason
(ConnectedWebsites -> Value)
-> (ConnectedWebsites -> Encoding)
-> ([ConnectedWebsites] -> Value)
-> ([ConnectedWebsites] -> Encoding)
-> ToJSON ConnectedWebsites
(ConnectedWebsite -> Value)
-> (ConnectedWebsite -> Encoding)
-> ([ConnectedWebsite] -> Value)
-> ([ConnectedWebsite] -> Encoding)
-> ToJSON ConnectedWebsite
(Sessions -> Value)
-> (Sessions -> Encoding)
-> ([Sessions] -> Value)
-> ([Sessions] -> Encoding)
-> ToJSON Sessions
(Session -> Value)
-> (Session -> Encoding)
-> ([Session] -> Value)
-> ([Session] -> Encoding)
-> ToJSON Session
(AccountTtl -> Value)
-> (AccountTtl -> Encoding)
-> ([AccountTtl] -> Value)
-> ([AccountTtl] -> Encoding)
-> ToJSON AccountTtl
(UserPrivacySetting -> Value)
-> (UserPrivacySetting -> Encoding)
-> ([UserPrivacySetting] -> Value)
-> ([UserPrivacySetting] -> Encoding)
-> ToJSON UserPrivacySetting
(UserPrivacySettingRules -> Value)
-> (UserPrivacySettingRules -> Encoding)
-> ([UserPrivacySettingRules] -> Value)
-> ([UserPrivacySettingRules] -> Encoding)
-> ToJSON UserPrivacySettingRules
(UserPrivacySettingRule -> Value)
-> (UserPrivacySettingRule -> Encoding)
-> ([UserPrivacySettingRule] -> Value)
-> ([UserPrivacySettingRule] -> Encoding)
-> ToJSON UserPrivacySettingRule
(JsonValue -> Value)
-> (JsonValue -> Encoding)
-> ([JsonValue] -> Value)
-> ([JsonValue] -> Encoding)
-> ToJSON JsonValue
(JsonObjectMember -> Value)
-> (JsonObjectMember -> Encoding)
-> ([JsonObjectMember] -> Value)
-> ([JsonObjectMember] -> Encoding)
-> ToJSON JsonObjectMember
(OptionValue -> Value)
-> (OptionValue -> Encoding)
-> ([OptionValue] -> Value)
-> ([OptionValue] -> Encoding)
-> ToJSON OptionValue
(NotificationGroup -> Value)
-> (NotificationGroup -> Encoding)
-> ([NotificationGroup] -> Value)
-> ([NotificationGroup] -> Encoding)
-> ToJSON NotificationGroup
(Notification -> Value)
-> (Notification -> Encoding)
-> ([Notification] -> Value)
-> ([Notification] -> Encoding)
-> ToJSON Notification
(NotificationGroupType -> Value)
-> (NotificationGroupType -> Encoding)
-> ([NotificationGroupType] -> Value)
-> ([NotificationGroupType] -> Encoding)
-> ToJSON NotificationGroupType
(NotificationType -> Value)
-> (NotificationType -> Encoding)
-> ([NotificationType] -> Value)
-> ([NotificationType] -> Encoding)
-> ToJSON NotificationType
(PushMessageContent -> Value)
-> (PushMessageContent -> Encoding)
-> ([PushMessageContent] -> Value)
-> ([PushMessageContent] -> Encoding)
-> ToJSON PushMessageContent
(CheckChatUsernameResult -> Value)
-> (CheckChatUsernameResult -> Encoding)
-> ([CheckChatUsernameResult] -> Value)
-> ([CheckChatUsernameResult] -> Encoding)
-> ToJSON CheckChatUsernameResult
(CanTransferOwnershipResult -> Value)
-> (CanTransferOwnershipResult -> Encoding)
-> ([CanTransferOwnershipResult] -> Value)
-> ([CanTransferOwnershipResult] -> Encoding)
-> ToJSON CanTransferOwnershipResult
(Hashtags -> Value)
-> (Hashtags -> Encoding)
-> ([Hashtags] -> Value)
-> ([Hashtags] -> Encoding)
-> ToJSON Hashtags
(InputBackground -> Value)
-> (InputBackground -> Encoding)
-> ([InputBackground] -> Value)
-> ([InputBackground] -> Encoding)
-> ToJSON InputBackground
(Backgrounds -> Value)
-> (Backgrounds -> Encoding)
-> ([Backgrounds] -> Value)
-> ([Backgrounds] -> Encoding)
-> ToJSON Backgrounds
(Background -> Value)
-> (Background -> Encoding)
-> ([Background] -> Value)
-> ([Background] -> Encoding)
-> ToJSON Background
(BackgroundType -> Value)
-> (BackgroundType -> Encoding)
-> ([BackgroundType] -> Value)
-> ([BackgroundType] -> Encoding)
-> ToJSON BackgroundType
(BackgroundFill -> Value)
-> (BackgroundFill -> Encoding)
-> ([BackgroundFill] -> Value)
-> ([BackgroundFill] -> Encoding)
-> ToJSON BackgroundFill
(PushReceiverId -> Value)
-> (PushReceiverId -> Encoding)
-> ([PushReceiverId] -> Value)
-> ([PushReceiverId] -> Encoding)
-> ToJSON PushReceiverId
(DeviceToken -> Value)
-> (DeviceToken -> Encoding)
-> ([DeviceToken] -> Value)
-> ([DeviceToken] -> Encoding)
-> ToJSON DeviceToken
(LocalizationTargetInfo -> Value)
-> (LocalizationTargetInfo -> Encoding)
-> ([LocalizationTargetInfo] -> Value)
-> ([LocalizationTargetInfo] -> Encoding)
-> ToJSON LocalizationTargetInfo
(LanguagePackInfo -> Value)
-> (LanguagePackInfo -> Encoding)
-> ([LanguagePackInfo] -> Value)
-> ([LanguagePackInfo] -> Encoding)
-> ToJSON LanguagePackInfo
(LanguagePackStrings -> Value)
-> (LanguagePackStrings -> Encoding)
-> ([LanguagePackStrings] -> Value)
-> ([LanguagePackStrings] -> Encoding)
-> ToJSON LanguagePackStrings
(LanguagePackString -> Value)
-> (LanguagePackString -> Encoding)
-> ([LanguagePackString] -> Value)
-> ([LanguagePackString] -> Encoding)
-> ToJSON LanguagePackString
(LanguagePackStringValue -> Value)
-> (LanguagePackStringValue -> Encoding)
-> ([LanguagePackStringValue] -> Value)
-> ([LanguagePackStringValue] -> Encoding)
-> ToJSON LanguagePackStringValue
(ChatEventLogFilters -> Value)
-> (ChatEventLogFilters -> Encoding)
-> ([ChatEventLogFilters] -> Value)
-> ([ChatEventLogFilters] -> Encoding)
-> ToJSON ChatEventLogFilters
(ChatEvents -> Value)
-> (ChatEvents -> Encoding)
-> ([ChatEvents] -> Value)
-> ([ChatEvents] -> Encoding)
-> ToJSON ChatEvents
(ChatEvent -> Value)
-> (ChatEvent -> Encoding)
-> ([ChatEvent] -> Value)
-> ([ChatEvent] -> Encoding)
-> ToJSON ChatEvent
(ChatEventAction -> Value)
-> (ChatEventAction -> Encoding)
-> ([ChatEventAction] -> Value)
-> ([ChatEventAction] -> Encoding)
-> ToJSON ChatEventAction
(GameHighScores -> Value)
-> (GameHighScores -> Encoding)
-> ([GameHighScores] -> Value)
-> ([GameHighScores] -> Encoding)
-> ToJSON GameHighScores
(GameHighScore -> Value)
-> (GameHighScore -> Encoding)
-> ([GameHighScore] -> Value)
-> ([GameHighScore] -> Encoding)
-> ToJSON GameHighScore
(CustomRequestResult -> Value)
-> (CustomRequestResult -> Encoding)
-> ([CustomRequestResult] -> Value)
-> ([CustomRequestResult] -> Encoding)
-> ToJSON CustomRequestResult
(CallbackQueryAnswer -> Value)
-> (CallbackQueryAnswer -> Encoding)
-> ([CallbackQueryAnswer] -> Value)
-> ([CallbackQueryAnswer] -> Encoding)
-> ToJSON CallbackQueryAnswer
(CallbackQueryPayload -> Value)
-> (CallbackQueryPayload -> Encoding)
-> ([CallbackQueryPayload] -> Value)
-> ([CallbackQueryPayload] -> Encoding)
-> ToJSON CallbackQueryPayload
(InlineQueryResults -> Value)
-> (InlineQueryResults -> Encoding)
-> ([InlineQueryResults] -> Value)
-> ([InlineQueryResults] -> Encoding)
-> ToJSON InlineQueryResults
(InlineQueryResult -> Value)
-> (InlineQueryResult -> Encoding)
-> ([InlineQueryResult] -> Value)
-> ([InlineQueryResult] -> Encoding)
-> ToJSON InlineQueryResult
(InputInlineQueryResult -> Value)
-> (InputInlineQueryResult -> Encoding)
-> ([InputInlineQueryResult] -> Value)
-> ([InputInlineQueryResult] -> Encoding)
-> ToJSON InputInlineQueryResult
(HttpUrl -> Value)
-> (HttpUrl -> Encoding)
-> ([HttpUrl] -> Value)
-> ([HttpUrl] -> Encoding)
-> ToJSON HttpUrl
(ImportedContacts -> Value)
-> (ImportedContacts -> Encoding)
-> ([ImportedContacts] -> Value)
-> ([ImportedContacts] -> Encoding)
-> ToJSON ImportedContacts
(Animations -> Value)
-> (Animations -> Encoding)
-> ([Animations] -> Value)
-> ([Animations] -> Encoding)
-> ToJSON Animations
(PhoneNumberAuthenticationSettings -> Value)
-> (PhoneNumberAuthenticationSettings -> Encoding)
-> ([PhoneNumberAuthenticationSettings] -> Value)
-> ([PhoneNumberAuthenticationSettings] -> Encoding)
-> ToJSON PhoneNumberAuthenticationSettings
(Call -> Value)
-> (Call -> Encoding)
-> ([Call] -> Value)
-> ([Call] -> Encoding)
-> ToJSON Call
(CallProblem -> Value)
-> (CallProblem -> Encoding)
-> ([CallProblem] -> Value)
-> ([CallProblem] -> Encoding)
-> ToJSON CallProblem
(CallState -> Value)
-> (CallState -> Encoding)
-> ([CallState] -> Value)
-> ([CallState] -> Encoding)
-> ToJSON CallState
(CallId -> Value)
-> (CallId -> Encoding)
-> ([CallId] -> Value)
-> ([CallId] -> Encoding)
-> ToJSON CallId
(CallConnection -> Value)
-> (CallConnection -> Encoding)
-> ([CallConnection] -> Value)
-> ([CallConnection] -> Encoding)
-> ToJSON CallConnection
(CallProtocol -> Value)
-> (CallProtocol -> Encoding)
-> ([CallProtocol] -> Value)
-> ([CallProtocol] -> Encoding)
-> ToJSON CallProtocol
(CallDiscardReason -> Value)
-> (CallDiscardReason -> Encoding)
-> ([CallDiscardReason] -> Value)
-> ([CallDiscardReason] -> Encoding)
-> ToJSON CallDiscardReason
(StickerSets -> Value)
-> (StickerSets -> Encoding)
-> ([StickerSets] -> Value)
-> ([StickerSets] -> Encoding)
-> ToJSON StickerSets
(StickerSetInfo -> Value)
-> (StickerSetInfo -> Encoding)
-> ([StickerSetInfo] -> Value)
-> ([StickerSetInfo] -> Encoding)
-> ToJSON StickerSetInfo
(StickerSet -> Value)
-> (StickerSet -> Encoding)
-> ([StickerSet] -> Value)
-> ([StickerSet] -> Encoding)
-> ToJSON StickerSet
(Emojis -> Value)
-> (Emojis -> Encoding)
-> ([Emojis] -> Value)
-> ([Emojis] -> Encoding)
-> ToJSON Emojis
(Stickers -> Value)
-> (Stickers -> Encoding)
-> ([Stickers] -> Value)
-> ([Stickers] -> Encoding)
-> ToJSON Stickers
(UserStatus -> Value)
-> (UserStatus -> Encoding)
-> ([UserStatus] -> Value)
-> ([UserStatus] -> Encoding)
-> ToJSON UserStatus
(ChatAction -> Value)
-> (ChatAction -> Encoding)
-> ([ChatAction] -> Value)
-> ([ChatAction] -> Encoding)
-> ToJSON ChatAction
(SearchMessagesFilter -> Value)
-> (SearchMessagesFilter -> Encoding)
-> ([SearchMessagesFilter] -> Value)
-> ([SearchMessagesFilter] -> Encoding)
-> ToJSON SearchMessagesFilter
(InputMessageContent -> Value)
-> (InputMessageContent -> Encoding)
-> ([InputMessageContent] -> Value)
-> ([InputMessageContent] -> Encoding)
-> ToJSON InputMessageContent
(SendMessageOptions -> Value)
-> (SendMessageOptions -> Encoding)
-> ([SendMessageOptions] -> Value)
-> ([SendMessageOptions] -> Encoding)
-> ToJSON SendMessageOptions
(MessageSchedulingState -> Value)
-> (MessageSchedulingState -> Encoding)
-> ([MessageSchedulingState] -> Value)
-> ([MessageSchedulingState] -> Encoding)
-> ToJSON MessageSchedulingState
(InputThumbnail -> Value)
-> (InputThumbnail -> Encoding)
-> ([InputThumbnail] -> Value)
-> ([InputThumbnail] -> Encoding)
-> ToJSON InputThumbnail
(TextEntityType -> Value)
-> (TextEntityType -> Encoding)
-> ([TextEntityType] -> Value)
-> ([TextEntityType] -> Encoding)
-> ToJSON TextEntityType
(MessageContent -> Value)
-> (MessageContent -> Encoding)
-> ([MessageContent] -> Value)
-> ([MessageContent] -> Encoding)
-> ToJSON MessageContent
(InputPassportElementError -> Value)
-> (InputPassportElementError -> Encoding)
-> ([InputPassportElementError] -> Value)
-> ([InputPassportElementError] -> Encoding)
-> ToJSON InputPassportElementError
(InputPassportElementErrorSource -> Value)
-> (InputPassportElementErrorSource -> Encoding)
-> ([InputPassportElementErrorSource] -> Value)
-> ([InputPassportElementErrorSource] -> Encoding)
-> ToJSON InputPassportElementErrorSource
(EncryptedPassportElement -> Value)
-> (EncryptedPassportElement -> Encoding)
-> ([EncryptedPassportElement] -> Value)
-> ([EncryptedPassportElement] -> Encoding)
-> ToJSON EncryptedPassportElement
(EncryptedCredentials -> Value)
-> (EncryptedCredentials -> Encoding)
-> ([EncryptedCredentials] -> Value)
-> ([EncryptedCredentials] -> Encoding)
-> ToJSON EncryptedCredentials
(PassportElementsWithErrors -> Value)
-> (PassportElementsWithErrors -> Encoding)
-> ([PassportElementsWithErrors] -> Value)
-> ([PassportElementsWithErrors] -> Encoding)
-> ToJSON PassportElementsWithErrors
(PassportAuthorizationForm -> Value)
-> (PassportAuthorizationForm -> Encoding)
-> ([PassportAuthorizationForm] -> Value)
-> ([PassportAuthorizationForm] -> Encoding)
-> ToJSON PassportAuthorizationForm
(PassportRequiredElement -> Value)
-> (PassportRequiredElement -> Encoding)
-> ([PassportRequiredElement] -> Value)
-> ([PassportRequiredElement] -> Encoding)
-> ToJSON PassportRequiredElement
(PassportSuitableElement -> Value)
-> (PassportSuitableElement -> Encoding)
-> ([PassportSuitableElement] -> Value)
-> ([PassportSuitableElement] -> Encoding)
-> ToJSON PassportSuitableElement
(PassportElementError -> Value)
-> (PassportElementError -> Encoding)
-> ([PassportElementError] -> Value)
-> ([PassportElementError] -> Encoding)
-> ToJSON PassportElementError
(PassportElementErrorSource -> Value)
-> (PassportElementErrorSource -> Encoding)
-> ([PassportElementErrorSource] -> Value)
-> ([PassportElementErrorSource] -> Encoding)
-> ToJSON PassportElementErrorSource
(PassportElements -> Value)
-> (PassportElements -> Encoding)
-> ([PassportElements] -> Value)
-> ([PassportElements] -> Encoding)
-> ToJSON PassportElements
(InputPassportElement -> Value)
-> (InputPassportElement -> Encoding)
-> ([InputPassportElement] -> Value)
-> ([InputPassportElement] -> Encoding)
-> ToJSON InputPassportElement
(PassportElement -> Value)
-> (PassportElement -> Encoding)
-> ([PassportElement] -> Value)
-> ([PassportElement] -> Encoding)
-> ToJSON PassportElement
(InputPersonalDocument -> Value)
-> (InputPersonalDocument -> Encoding)
-> ([InputPersonalDocument] -> Value)
-> ([InputPersonalDocument] -> Encoding)
-> ToJSON InputPersonalDocument
(PersonalDocument -> Value)
-> (PersonalDocument -> Encoding)
-> ([PersonalDocument] -> Value)
-> ([PersonalDocument] -> Encoding)
-> ToJSON PersonalDocument
(InputIdentityDocument -> Value)
-> (InputIdentityDocument -> Encoding)
-> ([InputIdentityDocument] -> Value)
-> ([InputIdentityDocument] -> Encoding)
-> ToJSON InputIdentityDocument
(IdentityDocument -> Value)
-> (IdentityDocument -> Encoding)
-> ([IdentityDocument] -> Value)
-> ([IdentityDocument] -> Encoding)
-> ToJSON IdentityDocument
(PersonalDetails -> Value)
-> (PersonalDetails -> Encoding)
-> ([PersonalDetails] -> Value)
-> ([PersonalDetails] -> Encoding)
-> ToJSON PersonalDetails
(Date -> Value)
-> (Date -> Encoding)
-> ([Date] -> Value)
-> ([Date] -> Encoding)
-> ToJSON Date
(PassportElementType -> Value)
-> (PassportElementType -> Encoding)
-> ([PassportElementType] -> Value)
-> ([PassportElementType] -> Encoding)
-> ToJSON PassportElementType
(DatedFile -> Value)
-> (DatedFile -> Encoding)
-> ([DatedFile] -> Value)
-> ([DatedFile] -> Encoding)
-> ToJSON DatedFile
(PaymentReceipt -> Value)
-> (PaymentReceipt -> Encoding)
-> ([PaymentReceipt] -> Value)
-> ([PaymentReceipt] -> Encoding)
-> ToJSON PaymentReceipt
(PaymentResult -> Value)
-> (PaymentResult -> Encoding)
-> ([PaymentResult] -> Value)
-> ([PaymentResult] -> Encoding)
-> ToJSON PaymentResult
(ValidatedOrderInfo -> Value)
-> (ValidatedOrderInfo -> Encoding)
-> ([ValidatedOrderInfo] -> Value)
-> ([ValidatedOrderInfo] -> Encoding)
-> ToJSON ValidatedOrderInfo
(PaymentForm -> Value)
-> (PaymentForm -> Encoding)
-> ([PaymentForm] -> Value)
-> ([PaymentForm] -> Encoding)
-> ToJSON PaymentForm
(PaymentsProviderStripe -> Value)
-> (PaymentsProviderStripe -> Encoding)
-> ([PaymentsProviderStripe] -> Value)
-> ([PaymentsProviderStripe] -> Encoding)
-> ToJSON PaymentsProviderStripe
(InputCredentials -> Value)
-> (InputCredentials -> Encoding)
-> ([InputCredentials] -> Value)
-> ([InputCredentials] -> Encoding)
-> ToJSON InputCredentials
(SavedCredentials -> Value)
-> (SavedCredentials -> Encoding)
-> ([SavedCredentials] -> Value)
-> ([SavedCredentials] -> Encoding)
-> ToJSON SavedCredentials
(ShippingOption -> Value)
-> (ShippingOption -> Encoding)
-> ([ShippingOption] -> Value)
-> ([ShippingOption] -> Encoding)
-> ToJSON ShippingOption
(OrderInfo -> Value)
-> (OrderInfo -> Encoding)
-> ([OrderInfo] -> Value)
-> ([OrderInfo] -> Encoding)
-> ToJSON OrderInfo
(Invoice -> Value)
-> (Invoice -> Encoding)
-> ([Invoice] -> Value)
-> ([Invoice] -> Encoding)
-> ToJSON Invoice
(LabeledPricePart -> Value)
-> (LabeledPricePart -> Encoding)
-> ([LabeledPricePart] -> Value)
-> ([LabeledPricePart] -> Encoding)
-> ToJSON LabeledPricePart
(Address -> Value)
-> (Address -> Encoding)
-> ([Address] -> Value)
-> ([Address] -> Encoding)
-> ToJSON Address
(BankCardInfo -> Value)
-> (BankCardInfo -> Encoding)
-> ([BankCardInfo] -> Value)
-> ([BankCardInfo] -> Encoding)
-> ToJSON BankCardInfo
(BankCardActionOpenUrl -> Value)
-> (BankCardActionOpenUrl -> Encoding)
-> ([BankCardActionOpenUrl] -> Value)
-> ([BankCardActionOpenUrl] -> Encoding)
-> ToJSON BankCardActionOpenUrl
(WebPage -> Value)
-> (WebPage -> Encoding)
-> ([WebPage] -> Value)
-> ([WebPage] -> Encoding)
-> ToJSON WebPage
(WebPageInstantView -> Value)
-> (WebPageInstantView -> Encoding)
-> ([WebPageInstantView] -> Value)
-> ([WebPageInstantView] -> Encoding)
-> ToJSON WebPageInstantView
(PageBlock -> Value)
-> (PageBlock -> Encoding)
-> ([PageBlock] -> Value)
-> ([PageBlock] -> Encoding)
-> ToJSON PageBlock
(PageBlockRelatedArticle -> Value)
-> (PageBlockRelatedArticle -> Encoding)
-> ([PageBlockRelatedArticle] -> Value)
-> ([PageBlockRelatedArticle] -> Encoding)
-> ToJSON PageBlockRelatedArticle
(PageBlockTableCell -> Value)
-> (PageBlockTableCell -> Encoding)
-> ([PageBlockTableCell] -> Value)
-> ([PageBlockTableCell] -> Encoding)
-> ToJSON PageBlockTableCell
(PageBlockVerticalAlignment -> Value)
-> (PageBlockVerticalAlignment -> Encoding)
-> ([PageBlockVerticalAlignment] -> Value)
-> ([PageBlockVerticalAlignment] -> Encoding)
-> ToJSON PageBlockVerticalAlignment
(PageBlockHorizontalAlignment -> Value)
-> (PageBlockHorizontalAlignment -> Encoding)
-> ([PageBlockHorizontalAlignment] -> Value)
-> ([PageBlockHorizontalAlignment] -> Encoding)
-> ToJSON PageBlockHorizontalAlignment
(PageBlockListItem -> Value)
-> (PageBlockListItem -> Encoding)
-> ([PageBlockListItem] -> Value)
-> ([PageBlockListItem] -> Encoding)
-> ToJSON PageBlockListItem
(PageBlockCaption -> Value)
-> (PageBlockCaption -> Encoding)
-> ([PageBlockCaption] -> Value)
-> ([PageBlockCaption] -> Encoding)
-> ToJSON PageBlockCaption
(RichText -> Value)
-> (RichText -> Encoding)
-> ([RichText] -> Value)
-> ([RichText] -> Encoding)
-> ToJSON RichText
(LoginUrlInfo -> Value)
-> (LoginUrlInfo -> Encoding)
-> ([LoginUrlInfo] -> Value)
-> ([LoginUrlInfo] -> Encoding)
-> ToJSON LoginUrlInfo
(ReplyMarkup -> Value)
-> (ReplyMarkup -> Encoding)
-> ([ReplyMarkup] -> Value)
-> ([ReplyMarkup] -> Encoding)
-> ToJSON ReplyMarkup
(InlineKeyboardButton -> Value)
-> (InlineKeyboardButton -> Encoding)
-> ([InlineKeyboardButton] -> Value)
-> ([InlineKeyboardButton] -> Encoding)
-> ToJSON InlineKeyboardButton
(InlineKeyboardButtonType -> Value)
-> (InlineKeyboardButtonType -> Encoding)
-> ([InlineKeyboardButtonType] -> Value)
-> ([InlineKeyboardButtonType] -> Encoding)
-> ToJSON InlineKeyboardButtonType
(KeyboardButton -> Value)
-> (KeyboardButton -> Encoding)
-> ([KeyboardButton] -> Value)
-> ([KeyboardButton] -> Encoding)
-> ToJSON KeyboardButton
(KeyboardButtonType -> Value)
-> (KeyboardButtonType -> Encoding)
-> ([KeyboardButtonType] -> Value)
-> ([KeyboardButtonType] -> Encoding)
-> ToJSON KeyboardButtonType
(ChatActionBar -> Value)
-> (ChatActionBar -> Encoding)
-> ([ChatActionBar] -> Value)
-> ([ChatActionBar] -> Encoding)
-> ToJSON ChatActionBar
(PublicChatType -> Value)
-> (PublicChatType -> Encoding)
-> ([PublicChatType] -> Value)
-> ([PublicChatType] -> Encoding)
-> ToJSON PublicChatType
(ChatInviteLinkInfo -> Value)
-> (ChatInviteLinkInfo -> Encoding)
-> ([ChatInviteLinkInfo] -> Value)
-> ([ChatInviteLinkInfo] -> Encoding)
-> ToJSON ChatInviteLinkInfo
(ChatInviteLink -> Value)
-> (ChatInviteLink -> Encoding)
-> ([ChatInviteLink] -> Value)
-> ([ChatInviteLink] -> Encoding)
-> ToJSON ChatInviteLink
(ChatsNearby -> Value)
-> (ChatsNearby -> Encoding)
-> ([ChatsNearby] -> Value)
-> ([ChatsNearby] -> Encoding)
-> ToJSON ChatsNearby
(ChatNearby -> Value)
-> (ChatNearby -> Encoding)
-> ([ChatNearby] -> Value)
-> ([ChatNearby] -> Encoding)
-> ToJSON ChatNearby
(Chats -> Value)
-> (Chats -> Encoding)
-> ([Chats] -> Value)
-> ([Chats] -> Encoding)
-> ToJSON Chats
(Chat -> Value)
-> (Chat -> Encoding)
-> ([Chat] -> Value)
-> ([Chat] -> Encoding)
-> ToJSON Chat
(ChatSource -> Value)
-> (ChatSource -> Encoding)
-> ([ChatSource] -> Value)
-> ([ChatSource] -> Encoding)
-> ToJSON ChatSource
(ChatList -> Value)
-> (ChatList -> Encoding)
-> ([ChatList] -> Value)
-> ([ChatList] -> Encoding)
-> ToJSON ChatList
(ChatType -> Value)
-> (ChatType -> Encoding)
-> ([ChatType] -> Value)
-> ([ChatType] -> Encoding)
-> ToJSON ChatType
(DraftMessage -> Value)
-> (DraftMessage -> Encoding)
-> ([DraftMessage] -> Value)
-> ([DraftMessage] -> Encoding)
-> ToJSON DraftMessage
(ScopeNotificationSettings -> Value)
-> (ScopeNotificationSettings -> Encoding)
-> ([ScopeNotificationSettings] -> Value)
-> ([ScopeNotificationSettings] -> Encoding)
-> ToJSON ScopeNotificationSettings
(ChatNotificationSettings -> Value)
-> (ChatNotificationSettings -> Encoding)
-> ([ChatNotificationSettings] -> Value)
-> ([ChatNotificationSettings] -> Encoding)
-> ToJSON ChatNotificationSettings
(NotificationSettingsScope -> Value)
-> (NotificationSettingsScope -> Encoding)
-> ([NotificationSettingsScope] -> Value)
-> ([NotificationSettingsScope] -> Encoding)
-> ToJSON NotificationSettingsScope
(FoundMessages -> Value)
-> (FoundMessages -> Encoding)
-> ([FoundMessages] -> Value)
-> ([FoundMessages] -> Encoding)
-> ToJSON FoundMessages
(Messages -> Value)
-> (Messages -> Encoding)
-> ([Messages] -> Value)
-> ([Messages] -> Encoding)
-> ToJSON Messages
(Message -> Value)
-> (Message -> Encoding)
-> ([Message] -> Value)
-> ([Message] -> Encoding)
-> ToJSON Message
(MessageSendingState -> Value)
-> (MessageSendingState -> Encoding)
-> ([MessageSendingState] -> Value)
-> ([MessageSendingState] -> Encoding)
-> ToJSON MessageSendingState
(MessageForwardInfo -> Value)
-> (MessageForwardInfo -> Encoding)
-> ([MessageForwardInfo] -> Value)
-> ([MessageForwardInfo] -> Encoding)
-> ToJSON MessageForwardInfo
(MessageForwardOrigin -> Value)
-> (MessageForwardOrigin -> Encoding)
-> ([MessageForwardOrigin] -> Value)
-> ([MessageForwardOrigin] -> Encoding)
-> ToJSON MessageForwardOrigin
(SecretChat -> Value)
-> (SecretChat -> Encoding)
-> ([SecretChat] -> Value)
-> ([SecretChat] -> Encoding)
-> ToJSON SecretChat
(SecretChatState -> Value)
-> (SecretChatState -> Encoding)
-> ([SecretChatState] -> Value)
-> ([SecretChatState] -> Encoding)
-> ToJSON SecretChatState
(SupergroupFullInfo -> Value)
-> (SupergroupFullInfo -> Encoding)
-> ([SupergroupFullInfo] -> Value)
-> ([SupergroupFullInfo] -> Encoding)
-> ToJSON SupergroupFullInfo
(Supergroup -> Value)
-> (Supergroup -> Encoding)
-> ([Supergroup] -> Value)
-> ([Supergroup] -> Encoding)
-> ToJSON Supergroup
(BasicGroupFullInfo -> Value)
-> (BasicGroupFullInfo -> Encoding)
-> ([BasicGroupFullInfo] -> Value)
-> ([BasicGroupFullInfo] -> Encoding)
-> ToJSON BasicGroupFullInfo
(BasicGroup -> Value)
-> (BasicGroup -> Encoding)
-> ([BasicGroup] -> Value)
-> ([BasicGroup] -> Encoding)
-> ToJSON BasicGroup
(SupergroupMembersFilter -> Value)
-> (SupergroupMembersFilter -> Encoding)
-> ([SupergroupMembersFilter] -> Value)
-> ([SupergroupMembersFilter] -> Encoding)
-> ToJSON SupergroupMembersFilter
(ChatMembersFilter -> Value)
-> (ChatMembersFilter -> Encoding)
-> ([ChatMembersFilter] -> Value)
-> ([ChatMembersFilter] -> Encoding)
-> ToJSON ChatMembersFilter
(ChatMembers -> Value)
-> (ChatMembers -> Encoding)
-> ([ChatMembers] -> Value)
-> ([ChatMembers] -> Encoding)
-> ToJSON ChatMembers
(ChatMember -> Value)
-> (ChatMember -> Encoding)
-> ([ChatMember] -> Value)
-> ([ChatMember] -> Encoding)
-> ToJSON ChatMember
(ChatMemberStatus -> Value)
-> (ChatMemberStatus -> Encoding)
-> ([ChatMemberStatus] -> Value)
-> ([ChatMemberStatus] -> Encoding)
-> ToJSON ChatMemberStatus
(ChatPermissions -> Value)
-> (ChatPermissions -> Encoding)
-> ([ChatPermissions] -> Value)
-> ([ChatPermissions] -> Encoding)
-> ToJSON ChatPermissions
(ChatAdministrators -> Value)
-> (ChatAdministrators -> Encoding)
-> ([ChatAdministrators] -> Value)
-> ([ChatAdministrators] -> Encoding)
-> ToJSON ChatAdministrators
(ChatAdministrator -> Value)
-> (ChatAdministrator -> Encoding)
-> ([ChatAdministrator] -> Value)
-> ([ChatAdministrator] -> Encoding)
-> ToJSON ChatAdministrator
(Users -> Value)
-> (Users -> Encoding)
-> ([Users] -> Value)
-> ([Users] -> Encoding)
-> ToJSON Users
(UserProfilePhotos -> Value)
-> (UserProfilePhotos -> Encoding)
-> ([UserProfilePhotos] -> Value)
-> ([UserProfilePhotos] -> Encoding)
-> ToJSON UserProfilePhotos
(UserProfilePhoto -> Value)
-> (UserProfilePhoto -> Encoding)
-> ([UserProfilePhoto] -> Value)
-> ([UserProfilePhoto] -> Encoding)
-> ToJSON UserProfilePhoto
(UserFullInfo -> Value)
-> (UserFullInfo -> Encoding)
-> ([UserFullInfo] -> Value)
-> ([UserFullInfo] -> Encoding)
-> ToJSON UserFullInfo
(User -> Value)
-> (User -> Encoding)
-> ([User] -> Value)
-> ([User] -> Encoding)
-> ToJSON User
(ChatLocation -> Value)
-> (ChatLocation -> Encoding)
-> ([ChatLocation] -> Value)
-> ([ChatLocation] -> Encoding)
-> ToJSON ChatLocation
(BotInfo -> Value)
-> (BotInfo -> Encoding)
-> ([BotInfo] -> Value)
-> ([BotInfo] -> Encoding)
-> ToJSON BotInfo
(BotCommand -> Value)
-> (BotCommand -> Encoding)
-> ([BotCommand] -> Value)
-> ([BotCommand] -> Encoding)
-> ToJSON BotCommand
(UserType -> Value)
-> (UserType -> Encoding)
-> ([UserType] -> Value)
-> ([UserType] -> Encoding)
-> ToJSON UserType
(ChatPhoto -> Value)
-> (ChatPhoto -> Encoding)
-> ([ChatPhoto] -> Value)
-> ([ChatPhoto] -> Encoding)
-> ToJSON ChatPhoto
(ProfilePhoto -> Value)
-> (ProfilePhoto -> Encoding)
-> ([ProfilePhoto] -> Value)
-> ([ProfilePhoto] -> Encoding)
-> ToJSON ProfilePhoto
(Poll -> Value)
-> (Poll -> Encoding)
-> ([Poll] -> Value)
-> ([Poll] -> Encoding)
-> ToJSON Poll
(Game -> Value)
-> (Game -> Encoding)
-> ([Game] -> Value)
-> ([Game] -> Encoding)
-> ToJSON Game
(Venue -> Value)
-> (Venue -> Encoding)
-> ([Venue] -> Value)
-> ([Venue] -> Encoding)
-> ToJSON Venue
(Location -> Value)
-> (Location -> Encoding)
-> ([Location] -> Value)
-> ([Location] -> Encoding)
-> ToJSON Location
(Contact -> Value)
-> (Contact -> Encoding)
-> ([Contact] -> Value)
-> ([Contact] -> Encoding)
-> ToJSON Contact
(VoiceNote -> Value)
-> (VoiceNote -> Encoding)
-> ([VoiceNote] -> Value)
-> ([VoiceNote] -> Encoding)
-> ToJSON VoiceNote
(VideoNote -> Value)
-> (VideoNote -> Encoding)
-> ([VideoNote] -> Value)
-> ([VideoNote] -> Encoding)
-> ToJSON VideoNote
(Video -> Value)
-> (Video -> Encoding)
-> ([Video] -> Value)
-> ([Video] -> Encoding)
-> ToJSON Video
(Sticker -> Value)
-> (Sticker -> Encoding)
-> ([Sticker] -> Value)
-> ([Sticker] -> Encoding)
-> ToJSON Sticker
(Photo -> Value)
-> (Photo -> Encoding)
-> ([Photo] -> Value)
-> ([Photo] -> Encoding)
-> ToJSON Photo
(Document -> Value)
-> (Document -> Encoding)
-> ([Document] -> Value)
-> ([Document] -> Encoding)
-> ToJSON Document
(Audio -> Value)
-> (Audio -> Encoding)
-> ([Audio] -> Value)
-> ([Audio] -> Encoding)
-> ToJSON Audio
(Animation -> Value)
-> (Animation -> Encoding)
-> ([Animation] -> Value)
-> ([Animation] -> Encoding)
-> ToJSON Animation
(PollType -> Value)
-> (PollType -> Encoding)
-> ([PollType] -> Value)
-> ([PollType] -> Encoding)
-> ToJSON PollType
(PollOption -> Value)
-> (PollOption -> Encoding)
-> ([PollOption] -> Value)
-> ([PollOption] -> Encoding)
-> ToJSON PollOption
(MaskPosition -> Value)
-> (MaskPosition -> Encoding)
-> ([MaskPosition] -> Value)
-> ([MaskPosition] -> Encoding)
-> ToJSON MaskPosition
(MaskPoint -> Value)
-> (MaskPoint -> Encoding)
-> ([MaskPoint] -> Value)
-> ([MaskPoint] -> Encoding)
-> ToJSON MaskPoint
(Minithumbnail -> Value)
-> (Minithumbnail -> Encoding)
-> ([Minithumbnail] -> Value)
-> ([Minithumbnail] -> Encoding)
-> ToJSON Minithumbnail
(PhotoSize -> Value)
-> (PhotoSize -> Encoding)
-> ([PhotoSize] -> Value)
-> ([PhotoSize] -> Encoding)
-> ToJSON PhotoSize
(InputFile -> Value)
-> (InputFile -> Encoding)
-> ([InputFile] -> Value)
-> ([InputFile] -> Encoding)
-> ToJSON InputFile
(File -> Value)
-> (File -> Encoding)
-> ([File] -> Value)
-> ([File] -> Encoding)
-> ToJSON File
(RemoteFile -> Value)
-> (RemoteFile -> Encoding)
-> ([RemoteFile] -> Value)
-> ([RemoteFile] -> Encoding)
-> ToJSON RemoteFile
(LocalFile -> Value)
-> (LocalFile -> Encoding)
-> ([LocalFile] -> Value)
-> ([LocalFile] -> Encoding)
-> ToJSON LocalFile
(TemporaryPasswordState -> Value)
-> (TemporaryPasswordState -> Encoding)
-> ([TemporaryPasswordState] -> Value)
-> ([TemporaryPasswordState] -> Encoding)
-> ToJSON TemporaryPasswordState
(RecoveryEmailAddress -> Value)
-> (RecoveryEmailAddress -> Encoding)
-> ([RecoveryEmailAddress] -> Value)
-> ([RecoveryEmailAddress] -> Encoding)
-> ToJSON RecoveryEmailAddress
(PasswordState -> Value)
-> (PasswordState -> Encoding)
-> ([PasswordState] -> Value)
-> ([PasswordState] -> Encoding)
-> ToJSON PasswordState
(AuthorizationState -> Value)
-> (AuthorizationState -> Encoding)
-> ([AuthorizationState] -> Value)
-> ([AuthorizationState] -> Encoding)
-> ToJSON AuthorizationState
(TermsOfService -> Value)
-> (TermsOfService -> Encoding)
-> ([TermsOfService] -> Value)
-> ([TermsOfService] -> Encoding)
-> ToJSON TermsOfService
(FormattedText -> Value)
-> (FormattedText -> Encoding)
-> ([FormattedText] -> Value)
-> ([FormattedText] -> Encoding)
-> ToJSON FormattedText
(TextEntities -> Value)
-> (TextEntities -> Encoding)
-> ([TextEntities] -> Value)
-> ([TextEntities] -> Encoding)
-> ToJSON TextEntities
(TextEntity -> Value)
-> (TextEntity -> Encoding)
-> ([TextEntity] -> Value)
-> ([TextEntity] -> Encoding)
-> ToJSON TextEntity
(EmailAddressAuthenticationCodeInfo -> Value)
-> (EmailAddressAuthenticationCodeInfo -> Encoding)
-> ([EmailAddressAuthenticationCodeInfo] -> Value)
-> ([EmailAddressAuthenticationCodeInfo] -> Encoding)
-> ToJSON EmailAddressAuthenticationCodeInfo
(AuthenticationCodeInfo -> Value)
-> (AuthenticationCodeInfo -> Encoding)
-> ([AuthenticationCodeInfo] -> Value)
-> ([AuthenticationCodeInfo] -> Encoding)
-> ToJSON AuthenticationCodeInfo
(AuthenticationCodeType -> Value)
-> (AuthenticationCodeType -> Encoding)
-> ([AuthenticationCodeType] -> Value)
-> ([AuthenticationCodeType] -> Encoding)
-> ToJSON AuthenticationCodeType
(TdlibParameters -> Value)
-> (TdlibParameters -> Encoding)
-> ([TdlibParameters] -> Value)
-> ([TdlibParameters] -> Encoding)
-> ToJSON TdlibParameters
(Ok -> Value)
-> (Ok -> Encoding)
-> ([Ok] -> Value)
-> ([Ok] -> Encoding)
-> ToJSON Ok
(Error -> Value)
-> (Error -> Encoding)
-> ([Error] -> Value)
-> ([Error] -> Encoding)
-> ToJSON Error
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
toEncodingList :: [Error] -> Encoding
$ctoEncodingList :: [Error] -> Encoding
toJSONList :: [Error] -> Value
$ctoJSONList :: [Error] -> Value
toEncoding :: Error -> Encoding
$ctoEncoding :: Error -> Encoding
toJSON :: Error -> Value
$ctoJSON :: Error -> Value
parseJSONList :: Value -> Parser [Error]
$cparseJSONList :: Value -> Parser [Error]
parseJSON :: Value -> Parser Error
$cparseJSON :: Value -> Parser Error
toEncodingList :: [Ok] -> Encoding
$ctoEncodingList :: [Ok] -> Encoding
toJSONList :: [Ok] -> Value
$ctoJSONList :: [Ok] -> Value
toEncoding :: Ok -> Encoding
$ctoEncoding :: Ok -> Encoding
toJSON :: Ok -> Value
$ctoJSON :: Ok -> Value
parseJSONList :: Value -> Parser [Ok]
$cparseJSONList :: Value -> Parser [Ok]
parseJSON :: Value -> Parser Ok
$cparseJSON :: Value -> Parser Ok
toEncodingList :: [TdlibParameters] -> Encoding
$ctoEncodingList :: [TdlibParameters] -> Encoding
toJSONList :: [TdlibParameters] -> Value
$ctoJSONList :: [TdlibParameters] -> Value
toEncoding :: TdlibParameters -> Encoding
$ctoEncoding :: TdlibParameters -> Encoding
toJSON :: TdlibParameters -> Value
$ctoJSON :: TdlibParameters -> Value
parseJSONList :: Value -> Parser [TdlibParameters]
$cparseJSONList :: Value -> Parser [TdlibParameters]
parseJSON :: Value -> Parser TdlibParameters
$cparseJSON :: Value -> Parser TdlibParameters
toEncodingList :: [AuthenticationCodeType] -> Encoding
$ctoEncodingList :: [AuthenticationCodeType] -> Encoding
toJSONList :: [AuthenticationCodeType] -> Value
$ctoJSONList :: [AuthenticationCodeType] -> Value
toEncoding :: AuthenticationCodeType -> Encoding
$ctoEncoding :: AuthenticationCodeType -> Encoding
toJSON :: AuthenticationCodeType -> Value
$ctoJSON :: AuthenticationCodeType -> Value
parseJSONList :: Value -> Parser [AuthenticationCodeType]
$cparseJSONList :: Value -> Parser [AuthenticationCodeType]
parseJSON :: Value -> Parser AuthenticationCodeType
$cparseJSON :: Value -> Parser AuthenticationCodeType
toEncodingList :: [AuthenticationCodeInfo] -> Encoding
$ctoEncodingList :: [AuthenticationCodeInfo] -> Encoding
toJSONList :: [AuthenticationCodeInfo] -> Value
$ctoJSONList :: [AuthenticationCodeInfo] -> Value
toEncoding :: AuthenticationCodeInfo -> Encoding
$ctoEncoding :: AuthenticationCodeInfo -> Encoding
toJSON :: AuthenticationCodeInfo -> Value
$ctoJSON :: AuthenticationCodeInfo -> Value
parseJSONList :: Value -> Parser [AuthenticationCodeInfo]
$cparseJSONList :: Value -> Parser [AuthenticationCodeInfo]
parseJSON :: Value -> Parser AuthenticationCodeInfo
$cparseJSON :: Value -> Parser AuthenticationCodeInfo
toEncodingList :: [EmailAddressAuthenticationCodeInfo] -> Encoding
$ctoEncodingList :: [EmailAddressAuthenticationCodeInfo] -> Encoding
toJSONList :: [EmailAddressAuthenticationCodeInfo] -> Value
$ctoJSONList :: [EmailAddressAuthenticationCodeInfo] -> Value
toEncoding :: EmailAddressAuthenticationCodeInfo -> Encoding
$ctoEncoding :: EmailAddressAuthenticationCodeInfo -> Encoding
toJSON :: EmailAddressAuthenticationCodeInfo -> Value
$ctoJSON :: EmailAddressAuthenticationCodeInfo -> Value
parseJSONList :: Value -> Parser [EmailAddressAuthenticationCodeInfo]
$cparseJSONList :: Value -> Parser [EmailAddressAuthenticationCodeInfo]
parseJSON :: Value -> Parser EmailAddressAuthenticationCodeInfo
$cparseJSON :: Value -> Parser EmailAddressAuthenticationCodeInfo
toEncodingList :: [TextEntity] -> Encoding
$ctoEncodingList :: [TextEntity] -> Encoding
toJSONList :: [TextEntity] -> Value
$ctoJSONList :: [TextEntity] -> Value
toEncoding :: TextEntity -> Encoding
$ctoEncoding :: TextEntity -> Encoding
toJSON :: TextEntity -> Value
$ctoJSON :: TextEntity -> Value
parseJSONList :: Value -> Parser [TextEntity]
$cparseJSONList :: Value -> Parser [TextEntity]
parseJSON :: Value -> Parser TextEntity
$cparseJSON :: Value -> Parser TextEntity
toEncodingList :: [TextEntities] -> Encoding
$ctoEncodingList :: [TextEntities] -> Encoding
toJSONList :: [TextEntities] -> Value
$ctoJSONList :: [TextEntities] -> Value
toEncoding :: TextEntities -> Encoding
$ctoEncoding :: TextEntities -> Encoding
toJSON :: TextEntities -> Value
$ctoJSON :: TextEntities -> Value
parseJSONList :: Value -> Parser [TextEntities]
$cparseJSONList :: Value -> Parser [TextEntities]
parseJSON :: Value -> Parser TextEntities
$cparseJSON :: Value -> Parser TextEntities
toEncodingList :: [FormattedText] -> Encoding
$ctoEncodingList :: [FormattedText] -> Encoding
toJSONList :: [FormattedText] -> Value
$ctoJSONList :: [FormattedText] -> Value
toEncoding :: FormattedText -> Encoding
$ctoEncoding :: FormattedText -> Encoding
toJSON :: FormattedText -> Value
$ctoJSON :: FormattedText -> Value
parseJSONList :: Value -> Parser [FormattedText]
$cparseJSONList :: Value -> Parser [FormattedText]
parseJSON :: Value -> Parser FormattedText
$cparseJSON :: Value -> Parser FormattedText
toEncodingList :: [TermsOfService] -> Encoding
$ctoEncodingList :: [TermsOfService] -> Encoding
toJSONList :: [TermsOfService] -> Value
$ctoJSONList :: [TermsOfService] -> Value
toEncoding :: TermsOfService -> Encoding
$ctoEncoding :: TermsOfService -> Encoding
toJSON :: TermsOfService -> Value
$ctoJSON :: TermsOfService -> Value
parseJSONList :: Value -> Parser [TermsOfService]
$cparseJSONList :: Value -> Parser [TermsOfService]
parseJSON :: Value -> Parser TermsOfService
$cparseJSON :: Value -> Parser TermsOfService
toEncodingList :: [AuthorizationState] -> Encoding
$ctoEncodingList :: [AuthorizationState] -> Encoding
toJSONList :: [AuthorizationState] -> Value
$ctoJSONList :: [AuthorizationState] -> Value
toEncoding :: AuthorizationState -> Encoding
$ctoEncoding :: AuthorizationState -> Encoding
toJSON :: AuthorizationState -> Value
$ctoJSON :: AuthorizationState -> Value
parseJSONList :: Value -> Parser [AuthorizationState]
$cparseJSONList :: Value -> Parser [AuthorizationState]
parseJSON :: Value -> Parser AuthorizationState
$cparseJSON :: Value -> Parser AuthorizationState
toEncodingList :: [PasswordState] -> Encoding
$ctoEncodingList :: [PasswordState] -> Encoding
toJSONList :: [PasswordState] -> Value
$ctoJSONList :: [PasswordState] -> Value
toEncoding :: PasswordState -> Encoding
$ctoEncoding :: PasswordState -> Encoding
toJSON :: PasswordState -> Value
$ctoJSON :: PasswordState -> Value
parseJSONList :: Value -> Parser [PasswordState]
$cparseJSONList :: Value -> Parser [PasswordState]
parseJSON :: Value -> Parser PasswordState
$cparseJSON :: Value -> Parser PasswordState
toEncodingList :: [RecoveryEmailAddress] -> Encoding
$ctoEncodingList :: [RecoveryEmailAddress] -> Encoding
toJSONList :: [RecoveryEmailAddress] -> Value
$ctoJSONList :: [RecoveryEmailAddress] -> Value
toEncoding :: RecoveryEmailAddress -> Encoding
$ctoEncoding :: RecoveryEmailAddress -> Encoding
toJSON :: RecoveryEmailAddress -> Value
$ctoJSON :: RecoveryEmailAddress -> Value
parseJSONList :: Value -> Parser [RecoveryEmailAddress]
$cparseJSONList :: Value -> Parser [RecoveryEmailAddress]
parseJSON :: Value -> Parser RecoveryEmailAddress
$cparseJSON :: Value -> Parser RecoveryEmailAddress
toEncodingList :: [TemporaryPasswordState] -> Encoding
$ctoEncodingList :: [TemporaryPasswordState] -> Encoding
toJSONList :: [TemporaryPasswordState] -> Value
$ctoJSONList :: [TemporaryPasswordState] -> Value
toEncoding :: TemporaryPasswordState -> Encoding
$ctoEncoding :: TemporaryPasswordState -> Encoding
toJSON :: TemporaryPasswordState -> Value
$ctoJSON :: TemporaryPasswordState -> Value
parseJSONList :: Value -> Parser [TemporaryPasswordState]
$cparseJSONList :: Value -> Parser [TemporaryPasswordState]
parseJSON :: Value -> Parser TemporaryPasswordState
$cparseJSON :: Value -> Parser TemporaryPasswordState
toEncodingList :: [LocalFile] -> Encoding
$ctoEncodingList :: [LocalFile] -> Encoding
toJSONList :: [LocalFile] -> Value
$ctoJSONList :: [LocalFile] -> Value
toEncoding :: LocalFile -> Encoding
$ctoEncoding :: LocalFile -> Encoding
toJSON :: LocalFile -> Value
$ctoJSON :: LocalFile -> Value
parseJSONList :: Value -> Parser [LocalFile]
$cparseJSONList :: Value -> Parser [LocalFile]
parseJSON :: Value -> Parser LocalFile
$cparseJSON :: Value -> Parser LocalFile
toEncodingList :: [RemoteFile] -> Encoding
$ctoEncodingList :: [RemoteFile] -> Encoding
toJSONList :: [RemoteFile] -> Value
$ctoJSONList :: [RemoteFile] -> Value
toEncoding :: RemoteFile -> Encoding
$ctoEncoding :: RemoteFile -> Encoding
toJSON :: RemoteFile -> Value
$ctoJSON :: RemoteFile -> Value
parseJSONList :: Value -> Parser [RemoteFile]
$cparseJSONList :: Value -> Parser [RemoteFile]
parseJSON :: Value -> Parser RemoteFile
$cparseJSON :: Value -> Parser RemoteFile
toEncodingList :: [File] -> Encoding
$ctoEncodingList :: [File] -> Encoding
toJSONList :: [File] -> Value
$ctoJSONList :: [File] -> Value
toEncoding :: File -> Encoding
$ctoEncoding :: File -> Encoding
toJSON :: File -> Value
$ctoJSON :: File -> Value
parseJSONList :: Value -> Parser [File]
$cparseJSONList :: Value -> Parser [File]
parseJSON :: Value -> Parser File
$cparseJSON :: Value -> Parser File
toEncodingList :: [InputFile] -> Encoding
$ctoEncodingList :: [InputFile] -> Encoding
toJSONList :: [InputFile] -> Value
$ctoJSONList :: [InputFile] -> Value
toEncoding :: InputFile -> Encoding
$ctoEncoding :: InputFile -> Encoding
toJSON :: InputFile -> Value
$ctoJSON :: InputFile -> Value
parseJSONList :: Value -> Parser [InputFile]
$cparseJSONList :: Value -> Parser [InputFile]
parseJSON :: Value -> Parser InputFile
$cparseJSON :: Value -> Parser InputFile
toEncodingList :: [PhotoSize] -> Encoding
$ctoEncodingList :: [PhotoSize] -> Encoding
toJSONList :: [PhotoSize] -> Value
$ctoJSONList :: [PhotoSize] -> Value
toEncoding :: PhotoSize -> Encoding
$ctoEncoding :: PhotoSize -> Encoding
toJSON :: PhotoSize -> Value
$ctoJSON :: PhotoSize -> Value
parseJSONList :: Value -> Parser [PhotoSize]
$cparseJSONList :: Value -> Parser [PhotoSize]
parseJSON :: Value -> Parser PhotoSize
$cparseJSON :: Value -> Parser PhotoSize
toEncodingList :: [Minithumbnail] -> Encoding
$ctoEncodingList :: [Minithumbnail] -> Encoding
toJSONList :: [Minithumbnail] -> Value
$ctoJSONList :: [Minithumbnail] -> Value
toEncoding :: Minithumbnail -> Encoding
$ctoEncoding :: Minithumbnail -> Encoding
toJSON :: Minithumbnail -> Value
$ctoJSON :: Minithumbnail -> Value
parseJSONList :: Value -> Parser [Minithumbnail]
$cparseJSONList :: Value -> Parser [Minithumbnail]
parseJSON :: Value -> Parser Minithumbnail
$cparseJSON :: Value -> Parser Minithumbnail
toEncodingList :: [MaskPoint] -> Encoding
$ctoEncodingList :: [MaskPoint] -> Encoding
toJSONList :: [MaskPoint] -> Value
$ctoJSONList :: [MaskPoint] -> Value
toEncoding :: MaskPoint -> Encoding
$ctoEncoding :: MaskPoint -> Encoding
toJSON :: MaskPoint -> Value
$ctoJSON :: MaskPoint -> Value
parseJSONList :: Value -> Parser [MaskPoint]
$cparseJSONList :: Value -> Parser [MaskPoint]
parseJSON :: Value -> Parser MaskPoint
$cparseJSON :: Value -> Parser MaskPoint
toEncodingList :: [MaskPosition] -> Encoding
$ctoEncodingList :: [MaskPosition] -> Encoding
toJSONList :: [MaskPosition] -> Value
$ctoJSONList :: [MaskPosition] -> Value
toEncoding :: MaskPosition -> Encoding
$ctoEncoding :: MaskPosition -> Encoding
toJSON :: MaskPosition -> Value
$ctoJSON :: MaskPosition -> Value
parseJSONList :: Value -> Parser [MaskPosition]
$cparseJSONList :: Value -> Parser [MaskPosition]
parseJSON :: Value -> Parser MaskPosition
$cparseJSON :: Value -> Parser MaskPosition
toEncodingList :: [PollOption] -> Encoding
$ctoEncodingList :: [PollOption] -> Encoding
toJSONList :: [PollOption] -> Value
$ctoJSONList :: [PollOption] -> Value
toEncoding :: PollOption -> Encoding
$ctoEncoding :: PollOption -> Encoding
toJSON :: PollOption -> Value
$ctoJSON :: PollOption -> Value
parseJSONList :: Value -> Parser [PollOption]
$cparseJSONList :: Value -> Parser [PollOption]
parseJSON :: Value -> Parser PollOption
$cparseJSON :: Value -> Parser PollOption
toEncodingList :: [PollType] -> Encoding
$ctoEncodingList :: [PollType] -> Encoding
toJSONList :: [PollType] -> Value
$ctoJSONList :: [PollType] -> Value
toEncoding :: PollType -> Encoding
$ctoEncoding :: PollType -> Encoding
toJSON :: PollType -> Value
$ctoJSON :: PollType -> Value
parseJSONList :: Value -> Parser [PollType]
$cparseJSONList :: Value -> Parser [PollType]
parseJSON :: Value -> Parser PollType
$cparseJSON :: Value -> Parser PollType
toEncodingList :: [Animation] -> Encoding
$ctoEncodingList :: [Animation] -> Encoding
toJSONList :: [Animation] -> Value
$ctoJSONList :: [Animation] -> Value
toEncoding :: Animation -> Encoding
$ctoEncoding :: Animation -> Encoding
toJSON :: Animation -> Value
$ctoJSON :: Animation -> Value
parseJSONList :: Value -> Parser [Animation]
$cparseJSONList :: Value -> Parser [Animation]
parseJSON :: Value -> Parser Animation
$cparseJSON :: Value -> Parser Animation
toEncodingList :: [Audio] -> Encoding
$ctoEncodingList :: [Audio] -> Encoding
toJSONList :: [Audio] -> Value
$ctoJSONList :: [Audio] -> Value
toEncoding :: Audio -> Encoding
$ctoEncoding :: Audio -> Encoding
toJSON :: Audio -> Value
$ctoJSON :: Audio -> Value
parseJSONList :: Value -> Parser [Audio]
$cparseJSONList :: Value -> Parser [Audio]
parseJSON :: Value -> Parser Audio
$cparseJSON :: Value -> Parser Audio
toEncodingList :: [Document] -> Encoding
$ctoEncodingList :: [Document] -> Encoding
toJSONList :: [Document] -> Value
$ctoJSONList :: [Document] -> Value
toEncoding :: Document -> Encoding
$ctoEncoding :: Document -> Encoding
toJSON :: Document -> Value
$ctoJSON :: Document -> Value
parseJSONList :: Value -> Parser [Document]
$cparseJSONList :: Value -> Parser [Document]
parseJSON :: Value -> Parser Document
$cparseJSON :: Value -> Parser Document
toEncodingList :: [Photo] -> Encoding
$ctoEncodingList :: [Photo] -> Encoding
toJSONList :: [Photo] -> Value
$ctoJSONList :: [Photo] -> Value
toEncoding :: Photo -> Encoding
$ctoEncoding :: Photo -> Encoding
toJSON :: Photo -> Value
$ctoJSON :: Photo -> Value
parseJSONList :: Value -> Parser [Photo]
$cparseJSONList :: Value -> Parser [Photo]
parseJSON :: Value -> Parser Photo
$cparseJSON :: Value -> Parser Photo
toEncodingList :: [Sticker] -> Encoding
$ctoEncodingList :: [Sticker] -> Encoding
toJSONList :: [Sticker] -> Value
$ctoJSONList :: [Sticker] -> Value
toEncoding :: Sticker -> Encoding
$ctoEncoding :: Sticker -> Encoding
toJSON :: Sticker -> Value
$ctoJSON :: Sticker -> Value
parseJSONList :: Value -> Parser [Sticker]
$cparseJSONList :: Value -> Parser [Sticker]
parseJSON :: Value -> Parser Sticker
$cparseJSON :: Value -> Parser Sticker
toEncodingList :: [Video] -> Encoding
$ctoEncodingList :: [Video] -> Encoding
toJSONList :: [Video] -> Value
$ctoJSONList :: [Video] -> Value
toEncoding :: Video -> Encoding
$ctoEncoding :: Video -> Encoding
toJSON :: Video -> Value
$ctoJSON :: Video -> Value
parseJSONList :: Value -> Parser [Video]
$cparseJSONList :: Value -> Parser [Video]
parseJSON :: Value -> Parser Video
$cparseJSON :: Value -> Parser Video
toEncodingList :: [VideoNote] -> Encoding
$ctoEncodingList :: [VideoNote] -> Encoding
toJSONList :: [VideoNote] -> Value
$ctoJSONList :: [VideoNote] -> Value
toEncoding :: VideoNote -> Encoding
$ctoEncoding :: VideoNote -> Encoding
toJSON :: VideoNote -> Value
$ctoJSON :: VideoNote -> Value
parseJSONList :: Value -> Parser [VideoNote]
$cparseJSONList :: Value -> Parser [VideoNote]
parseJSON :: Value -> Parser VideoNote
$cparseJSON :: Value -> Parser VideoNote
toEncodingList :: [VoiceNote] -> Encoding
$ctoEncodingList :: [VoiceNote] -> Encoding
toJSONList :: [VoiceNote] -> Value
$ctoJSONList :: [VoiceNote] -> Value
toEncoding :: VoiceNote -> Encoding
$ctoEncoding :: VoiceNote -> Encoding
toJSON :: VoiceNote -> Value
$ctoJSON :: VoiceNote -> Value
parseJSONList :: Value -> Parser [VoiceNote]
$cparseJSONList :: Value -> Parser [VoiceNote]
parseJSON :: Value -> Parser VoiceNote
$cparseJSON :: Value -> Parser VoiceNote
toEncodingList :: [Contact] -> Encoding
$ctoEncodingList :: [Contact] -> Encoding
toJSONList :: [Contact] -> Value
$ctoJSONList :: [Contact] -> Value
toEncoding :: Contact -> Encoding
$ctoEncoding :: Contact -> Encoding
toJSON :: Contact -> Value
$ctoJSON :: Contact -> Value
parseJSONList :: Value -> Parser [Contact]
$cparseJSONList :: Value -> Parser [Contact]
parseJSON :: Value -> Parser Contact
$cparseJSON :: Value -> Parser Contact
toEncodingList :: [Location] -> Encoding
$ctoEncodingList :: [Location] -> Encoding
toJSONList :: [Location] -> Value
$ctoJSONList :: [Location] -> Value
toEncoding :: Location -> Encoding
$ctoEncoding :: Location -> Encoding
toJSON :: Location -> Value
$ctoJSON :: Location -> Value
parseJSONList :: Value -> Parser [Location]
$cparseJSONList :: Value -> Parser [Location]
parseJSON :: Value -> Parser Location
$cparseJSON :: Value -> Parser Location
toEncodingList :: [Venue] -> Encoding
$ctoEncodingList :: [Venue] -> Encoding
toJSONList :: [Venue] -> Value
$ctoJSONList :: [Venue] -> Value
toEncoding :: Venue -> Encoding
$ctoEncoding :: Venue -> Encoding
toJSON :: Venue -> Value
$ctoJSON :: Venue -> Value
parseJSONList :: Value -> Parser [Venue]
$cparseJSONList :: Value -> Parser [Venue]
parseJSON :: Value -> Parser Venue
$cparseJSON :: Value -> Parser Venue
toEncodingList :: [Game] -> Encoding
$ctoEncodingList :: [Game] -> Encoding
toJSONList :: [Game] -> Value
$ctoJSONList :: [Game] -> Value
toEncoding :: Game -> Encoding
$ctoEncoding :: Game -> Encoding
toJSON :: Game -> Value
$ctoJSON :: Game -> Value
parseJSONList :: Value -> Parser [Game]
$cparseJSONList :: Value -> Parser [Game]
parseJSON :: Value -> Parser Game
$cparseJSON :: Value -> Parser Game
toEncodingList :: [Poll] -> Encoding
$ctoEncodingList :: [Poll] -> Encoding
toJSONList :: [Poll] -> Value
$ctoJSONList :: [Poll] -> Value
toEncoding :: Poll -> Encoding
$ctoEncoding :: Poll -> Encoding
toJSON :: Poll -> Value
$ctoJSON :: Poll -> Value
parseJSONList :: Value -> Parser [Poll]
$cparseJSONList :: Value -> Parser [Poll]
parseJSON :: Value -> Parser Poll
$cparseJSON :: Value -> Parser Poll
toEncodingList :: [ProfilePhoto] -> Encoding
$ctoEncodingList :: [ProfilePhoto] -> Encoding
toJSONList :: [ProfilePhoto] -> Value
$ctoJSONList :: [ProfilePhoto] -> Value
toEncoding :: ProfilePhoto -> Encoding
$ctoEncoding :: ProfilePhoto -> Encoding
toJSON :: ProfilePhoto -> Value
$ctoJSON :: ProfilePhoto -> Value
parseJSONList :: Value -> Parser [ProfilePhoto]
$cparseJSONList :: Value -> Parser [ProfilePhoto]
parseJSON :: Value -> Parser ProfilePhoto
$cparseJSON :: Value -> Parser ProfilePhoto
toEncodingList :: [ChatPhoto] -> Encoding
$ctoEncodingList :: [ChatPhoto] -> Encoding
toJSONList :: [ChatPhoto] -> Value
$ctoJSONList :: [ChatPhoto] -> Value
toEncoding :: ChatPhoto -> Encoding
$ctoEncoding :: ChatPhoto -> Encoding
toJSON :: ChatPhoto -> Value
$ctoJSON :: ChatPhoto -> Value
parseJSONList :: Value -> Parser [ChatPhoto]
$cparseJSONList :: Value -> Parser [ChatPhoto]
parseJSON :: Value -> Parser ChatPhoto
$cparseJSON :: Value -> Parser ChatPhoto
toEncodingList :: [UserType] -> Encoding
$ctoEncodingList :: [UserType] -> Encoding
toJSONList :: [UserType] -> Value
$ctoJSONList :: [UserType] -> Value
toEncoding :: UserType -> Encoding
$ctoEncoding :: UserType -> Encoding
toJSON :: UserType -> Value
$ctoJSON :: UserType -> Value
parseJSONList :: Value -> Parser [UserType]
$cparseJSONList :: Value -> Parser [UserType]
parseJSON :: Value -> Parser UserType
$cparseJSON :: Value -> Parser UserType
toEncodingList :: [BotCommand] -> Encoding
$ctoEncodingList :: [BotCommand] -> Encoding
toJSONList :: [BotCommand] -> Value
$ctoJSONList :: [BotCommand] -> Value
toEncoding :: BotCommand -> Encoding
$ctoEncoding :: BotCommand -> Encoding
toJSON :: BotCommand -> Value
$ctoJSON :: BotCommand -> Value
parseJSONList :: Value -> Parser [BotCommand]
$cparseJSONList :: Value -> Parser [BotCommand]
parseJSON :: Value -> Parser BotCommand
$cparseJSON :: Value -> Parser BotCommand
toEncodingList :: [BotInfo] -> Encoding
$ctoEncodingList :: [BotInfo] -> Encoding
toJSONList :: [BotInfo] -> Value
$ctoJSONList :: [BotInfo] -> Value
toEncoding :: BotInfo -> Encoding
$ctoEncoding :: BotInfo -> Encoding
toJSON :: BotInfo -> Value
$ctoJSON :: BotInfo -> Value
parseJSONList :: Value -> Parser [BotInfo]
$cparseJSONList :: Value -> Parser [BotInfo]
parseJSON :: Value -> Parser BotInfo
$cparseJSON :: Value -> Parser BotInfo
toEncodingList :: [ChatLocation] -> Encoding
$ctoEncodingList :: [ChatLocation] -> Encoding
toJSONList :: [ChatLocation] -> Value
$ctoJSONList :: [ChatLocation] -> Value
toEncoding :: ChatLocation -> Encoding
$ctoEncoding :: ChatLocation -> Encoding
toJSON :: ChatLocation -> Value
$ctoJSON :: ChatLocation -> Value
parseJSONList :: Value -> Parser [ChatLocation]
$cparseJSONList :: Value -> Parser [ChatLocation]
parseJSON :: Value -> Parser ChatLocation
$cparseJSON :: Value -> Parser ChatLocation
toEncodingList :: [User] -> Encoding
$ctoEncodingList :: [User] -> Encoding
toJSONList :: [User] -> Value
$ctoJSONList :: [User] -> Value
toEncoding :: User -> Encoding
$ctoEncoding :: User -> Encoding
toJSON :: User -> Value
$ctoJSON :: User -> Value
parseJSONList :: Value -> Parser [User]
$cparseJSONList :: Value -> Parser [User]
parseJSON :: Value -> Parser User
$cparseJSON :: Value -> Parser User
toEncodingList :: [UserFullInfo] -> Encoding
$ctoEncodingList :: [UserFullInfo] -> Encoding
toJSONList :: [UserFullInfo] -> Value
$ctoJSONList :: [UserFullInfo] -> Value
toEncoding :: UserFullInfo -> Encoding
$ctoEncoding :: UserFullInfo -> Encoding
toJSON :: UserFullInfo -> Value
$ctoJSON :: UserFullInfo -> Value
parseJSONList :: Value -> Parser [UserFullInfo]
$cparseJSONList :: Value -> Parser [UserFullInfo]
parseJSON :: Value -> Parser UserFullInfo
$cparseJSON :: Value -> Parser UserFullInfo
toEncodingList :: [UserProfilePhoto] -> Encoding
$ctoEncodingList :: [UserProfilePhoto] -> Encoding
toJSONList :: [UserProfilePhoto] -> Value
$ctoJSONList :: [UserProfilePhoto] -> Value
toEncoding :: UserProfilePhoto -> Encoding
$ctoEncoding :: UserProfilePhoto -> Encoding
toJSON :: UserProfilePhoto -> Value
$ctoJSON :: UserProfilePhoto -> Value
parseJSONList :: Value -> Parser [UserProfilePhoto]
$cparseJSONList :: Value -> Parser [UserProfilePhoto]
parseJSON :: Value -> Parser UserProfilePhoto
$cparseJSON :: Value -> Parser UserProfilePhoto
toEncodingList :: [UserProfilePhotos] -> Encoding
$ctoEncodingList :: [UserProfilePhotos] -> Encoding
toJSONList :: [UserProfilePhotos] -> Value
$ctoJSONList :: [UserProfilePhotos] -> Value
toEncoding :: UserProfilePhotos -> Encoding
$ctoEncoding :: UserProfilePhotos -> Encoding
toJSON :: UserProfilePhotos -> Value
$ctoJSON :: UserProfilePhotos -> Value
parseJSONList :: Value -> Parser [UserProfilePhotos]
$cparseJSONList :: Value -> Parser [UserProfilePhotos]
parseJSON :: Value -> Parser UserProfilePhotos
$cparseJSON :: Value -> Parser UserProfilePhotos
toEncodingList :: [Users] -> Encoding
$ctoEncodingList :: [Users] -> Encoding
toJSONList :: [Users] -> Value
$ctoJSONList :: [Users] -> Value
toEncoding :: Users -> Encoding
$ctoEncoding :: Users -> Encoding
toJSON :: Users -> Value
$ctoJSON :: Users -> Value
parseJSONList :: Value -> Parser [Users]
$cparseJSONList :: Value -> Parser [Users]
parseJSON :: Value -> Parser Users
$cparseJSON :: Value -> Parser Users
toEncodingList :: [ChatAdministrator] -> Encoding
$ctoEncodingList :: [ChatAdministrator] -> Encoding
toJSONList :: [ChatAdministrator] -> Value
$ctoJSONList :: [ChatAdministrator] -> Value
toEncoding :: ChatAdministrator -> Encoding
$ctoEncoding :: ChatAdministrator -> Encoding
toJSON :: ChatAdministrator -> Value
$ctoJSON :: ChatAdministrator -> Value
parseJSONList :: Value -> Parser [ChatAdministrator]
$cparseJSONList :: Value -> Parser [ChatAdministrator]
parseJSON :: Value -> Parser ChatAdministrator
$cparseJSON :: Value -> Parser ChatAdministrator
toEncodingList :: [ChatAdministrators] -> Encoding
$ctoEncodingList :: [ChatAdministrators] -> Encoding
toJSONList :: [ChatAdministrators] -> Value
$ctoJSONList :: [ChatAdministrators] -> Value
toEncoding :: ChatAdministrators -> Encoding
$ctoEncoding :: ChatAdministrators -> Encoding
toJSON :: ChatAdministrators -> Value
$ctoJSON :: ChatAdministrators -> Value
parseJSONList :: Value -> Parser [ChatAdministrators]
$cparseJSONList :: Value -> Parser [ChatAdministrators]
parseJSON :: Value -> Parser ChatAdministrators
$cparseJSON :: Value -> Parser ChatAdministrators
toEncodingList :: [ChatPermissions] -> Encoding
$ctoEncodingList :: [ChatPermissions] -> Encoding
toJSONList :: [ChatPermissions] -> Value
$ctoJSONList :: [ChatPermissions] -> Value
toEncoding :: ChatPermissions -> Encoding
$ctoEncoding :: ChatPermissions -> Encoding
toJSON :: ChatPermissions -> Value
$ctoJSON :: ChatPermissions -> Value
parseJSONList :: Value -> Parser [ChatPermissions]
$cparseJSONList :: Value -> Parser [ChatPermissions]
parseJSON :: Value -> Parser ChatPermissions
$cparseJSON :: Value -> Parser ChatPermissions
toEncodingList :: [ChatMemberStatus] -> Encoding
$ctoEncodingList :: [ChatMemberStatus] -> Encoding
toJSONList :: [ChatMemberStatus] -> Value
$ctoJSONList :: [ChatMemberStatus] -> Value
toEncoding :: ChatMemberStatus -> Encoding
$ctoEncoding :: ChatMemberStatus -> Encoding
toJSON :: ChatMemberStatus -> Value
$ctoJSON :: ChatMemberStatus -> Value
parseJSONList :: Value -> Parser [ChatMemberStatus]
$cparseJSONList :: Value -> Parser [ChatMemberStatus]
parseJSON :: Value -> Parser ChatMemberStatus
$cparseJSON :: Value -> Parser ChatMemberStatus
toEncodingList :: [ChatMember] -> Encoding
$ctoEncodingList :: [ChatMember] -> Encoding
toJSONList :: [ChatMember] -> Value
$ctoJSONList :: [ChatMember] -> Value
toEncoding :: ChatMember -> Encoding
$ctoEncoding :: ChatMember -> Encoding
toJSON :: ChatMember -> Value
$ctoJSON :: ChatMember -> Value
parseJSONList :: Value -> Parser [ChatMember]
$cparseJSONList :: Value -> Parser [ChatMember]
parseJSON :: Value -> Parser ChatMember
$cparseJSON :: Value -> Parser ChatMember
toEncodingList :: [ChatMembers] -> Encoding
$ctoEncodingList :: [ChatMembers] -> Encoding
toJSONList :: [ChatMembers] -> Value
$ctoJSONList :: [ChatMembers] -> Value
toEncoding :: ChatMembers -> Encoding
$ctoEncoding :: ChatMembers -> Encoding
toJSON :: ChatMembers -> Value
$ctoJSON :: ChatMembers -> Value
parseJSONList :: Value -> Parser [ChatMembers]
$cparseJSONList :: Value -> Parser [ChatMembers]
parseJSON :: Value -> Parser ChatMembers
$cparseJSON :: Value -> Parser ChatMembers
toEncodingList :: [ChatMembersFilter] -> Encoding
$ctoEncodingList :: [ChatMembersFilter] -> Encoding
toJSONList :: [ChatMembersFilter] -> Value
$ctoJSONList :: [ChatMembersFilter] -> Value
toEncoding :: ChatMembersFilter -> Encoding
$ctoEncoding :: ChatMembersFilter -> Encoding
toJSON :: ChatMembersFilter -> Value
$ctoJSON :: ChatMembersFilter -> Value
parseJSONList :: Value -> Parser [ChatMembersFilter]
$cparseJSONList :: Value -> Parser [ChatMembersFilter]
parseJSON :: Value -> Parser ChatMembersFilter
$cparseJSON :: Value -> Parser ChatMembersFilter
toEncodingList :: [SupergroupMembersFilter] -> Encoding
$ctoEncodingList :: [SupergroupMembersFilter] -> Encoding
toJSONList :: [SupergroupMembersFilter] -> Value
$ctoJSONList :: [SupergroupMembersFilter] -> Value
toEncoding :: SupergroupMembersFilter -> Encoding
$ctoEncoding :: SupergroupMembersFilter -> Encoding
toJSON :: SupergroupMembersFilter -> Value
$ctoJSON :: SupergroupMembersFilter -> Value
parseJSONList :: Value -> Parser [SupergroupMembersFilter]
$cparseJSONList :: Value -> Parser [SupergroupMembersFilter]
parseJSON :: Value -> Parser SupergroupMembersFilter
$cparseJSON :: Value -> Parser SupergroupMembersFilter
toEncodingList :: [BasicGroup] -> Encoding
$ctoEncodingList :: [BasicGroup] -> Encoding
toJSONList :: [BasicGroup] -> Value
$ctoJSONList :: [BasicGroup] -> Value
toEncoding :: BasicGroup -> Encoding
$ctoEncoding :: BasicGroup -> Encoding
toJSON :: BasicGroup -> Value
$ctoJSON :: BasicGroup -> Value
parseJSONList :: Value -> Parser [BasicGroup]
$cparseJSONList :: Value -> Parser [BasicGroup]
parseJSON :: Value -> Parser BasicGroup
$cparseJSON :: Value -> Parser BasicGroup
toEncodingList :: [BasicGroupFullInfo] -> Encoding
$ctoEncodingList :: [BasicGroupFullInfo] -> Encoding
toJSONList :: [BasicGroupFullInfo] -> Value
$ctoJSONList :: [BasicGroupFullInfo] -> Value
toEncoding :: BasicGroupFullInfo -> Encoding
$ctoEncoding :: BasicGroupFullInfo -> Encoding
toJSON :: BasicGroupFullInfo -> Value
$ctoJSON :: BasicGroupFullInfo -> Value
parseJSONList :: Value -> Parser [BasicGroupFullInfo]
$cparseJSONList :: Value -> Parser [BasicGroupFullInfo]
parseJSON :: Value -> Parser BasicGroupFullInfo
$cparseJSON :: Value -> Parser BasicGroupFullInfo
toEncodingList :: [Supergroup] -> Encoding
$ctoEncodingList :: [Supergroup] -> Encoding
toJSONList :: [Supergroup] -> Value
$ctoJSONList :: [Supergroup] -> Value
toEncoding :: Supergroup -> Encoding
$ctoEncoding :: Supergroup -> Encoding
toJSON :: Supergroup -> Value
$ctoJSON :: Supergroup -> Value
parseJSONList :: Value -> Parser [Supergroup]
$cparseJSONList :: Value -> Parser [Supergroup]
parseJSON :: Value -> Parser Supergroup
$cparseJSON :: Value -> Parser Supergroup
toEncodingList :: [SupergroupFullInfo] -> Encoding
$ctoEncodingList :: [SupergroupFullInfo] -> Encoding
toJSONList :: [SupergroupFullInfo] -> Value
$ctoJSONList :: [SupergroupFullInfo] -> Value
toEncoding :: SupergroupFullInfo -> Encoding
$ctoEncoding :: SupergroupFullInfo -> Encoding
toJSON :: SupergroupFullInfo -> Value
$ctoJSON :: SupergroupFullInfo -> Value
parseJSONList :: Value -> Parser [SupergroupFullInfo]
$cparseJSONList :: Value -> Parser [SupergroupFullInfo]
parseJSON :: Value -> Parser SupergroupFullInfo
$cparseJSON :: Value -> Parser SupergroupFullInfo
toEncodingList :: [SecretChatState] -> Encoding
$ctoEncodingList :: [SecretChatState] -> Encoding
toJSONList :: [SecretChatState] -> Value
$ctoJSONList :: [SecretChatState] -> Value
toEncoding :: SecretChatState -> Encoding
$ctoEncoding :: SecretChatState -> Encoding
toJSON :: SecretChatState -> Value
$ctoJSON :: SecretChatState -> Value
parseJSONList :: Value -> Parser [SecretChatState]
$cparseJSONList :: Value -> Parser [SecretChatState]
parseJSON :: Value -> Parser SecretChatState
$cparseJSON :: Value -> Parser SecretChatState
toEncodingList :: [SecretChat] -> Encoding
$ctoEncodingList :: [SecretChat] -> Encoding
toJSONList :: [SecretChat] -> Value
$ctoJSONList :: [SecretChat] -> Value
toEncoding :: SecretChat -> Encoding
$ctoEncoding :: SecretChat -> Encoding
toJSON :: SecretChat -> Value
$ctoJSON :: SecretChat -> Value
parseJSONList :: Value -> Parser [SecretChat]
$cparseJSONList :: Value -> Parser [SecretChat]
parseJSON :: Value -> Parser SecretChat
$cparseJSON :: Value -> Parser SecretChat
toEncodingList :: [MessageForwardOrigin] -> Encoding
$ctoEncodingList :: [MessageForwardOrigin] -> Encoding
toJSONList :: [MessageForwardOrigin] -> Value
$ctoJSONList :: [MessageForwardOrigin] -> Value
toEncoding :: MessageForwardOrigin -> Encoding
$ctoEncoding :: MessageForwardOrigin -> Encoding
toJSON :: MessageForwardOrigin -> Value
$ctoJSON :: MessageForwardOrigin -> Value
parseJSONList :: Value -> Parser [MessageForwardOrigin]
$cparseJSONList :: Value -> Parser [MessageForwardOrigin]
parseJSON :: Value -> Parser MessageForwardOrigin
$cparseJSON :: Value -> Parser MessageForwardOrigin
toEncodingList :: [MessageForwardInfo] -> Encoding
$ctoEncodingList :: [MessageForwardInfo] -> Encoding
toJSONList :: [MessageForwardInfo] -> Value
$ctoJSONList :: [MessageForwardInfo] -> Value
toEncoding :: MessageForwardInfo -> Encoding
$ctoEncoding :: MessageForwardInfo -> Encoding
toJSON :: MessageForwardInfo -> Value
$ctoJSON :: MessageForwardInfo -> Value
parseJSONList :: Value -> Parser [MessageForwardInfo]
$cparseJSONList :: Value -> Parser [MessageForwardInfo]
parseJSON :: Value -> Parser MessageForwardInfo
$cparseJSON :: Value -> Parser MessageForwardInfo
toEncodingList :: [MessageSendingState] -> Encoding
$ctoEncodingList :: [MessageSendingState] -> Encoding
toJSONList :: [MessageSendingState] -> Value
$ctoJSONList :: [MessageSendingState] -> Value
toEncoding :: MessageSendingState -> Encoding
$ctoEncoding :: MessageSendingState -> Encoding
toJSON :: MessageSendingState -> Value
$ctoJSON :: MessageSendingState -> Value
parseJSONList :: Value -> Parser [MessageSendingState]
$cparseJSONList :: Value -> Parser [MessageSendingState]
parseJSON :: Value -> Parser MessageSendingState
$cparseJSON :: Value -> Parser MessageSendingState
toEncodingList :: [Message] -> Encoding
$ctoEncodingList :: [Message] -> Encoding
toJSONList :: [Message] -> Value
$ctoJSONList :: [Message] -> Value
toEncoding :: Message -> Encoding
$ctoEncoding :: Message -> Encoding
toJSON :: Message -> Value
$ctoJSON :: Message -> Value
parseJSONList :: Value -> Parser [Message]
$cparseJSONList :: Value -> Parser [Message]
parseJSON :: Value -> Parser Message
$cparseJSON :: Value -> Parser Message
toEncodingList :: [Messages] -> Encoding
$ctoEncodingList :: [Messages] -> Encoding
toJSONList :: [Messages] -> Value
$ctoJSONList :: [Messages] -> Value
toEncoding :: Messages -> Encoding
$ctoEncoding :: Messages -> Encoding
toJSON :: Messages -> Value
$ctoJSON :: Messages -> Value
parseJSONList :: Value -> Parser [Messages]
$cparseJSONList :: Value -> Parser [Messages]
parseJSON :: Value -> Parser Messages
$cparseJSON :: Value -> Parser Messages
toEncodingList :: [FoundMessages] -> Encoding
$ctoEncodingList :: [FoundMessages] -> Encoding
toJSONList :: [FoundMessages] -> Value
$ctoJSONList :: [FoundMessages] -> Value
toEncoding :: FoundMessages -> Encoding
$ctoEncoding :: FoundMessages -> Encoding
toJSON :: FoundMessages -> Value
$ctoJSON :: FoundMessages -> Value
parseJSONList :: Value -> Parser [FoundMessages]
$cparseJSONList :: Value -> Parser [FoundMessages]
parseJSON :: Value -> Parser FoundMessages
$cparseJSON :: Value -> Parser FoundMessages
toEncodingList :: [NotificationSettingsScope] -> Encoding
$ctoEncodingList :: [NotificationSettingsScope] -> Encoding
toJSONList :: [NotificationSettingsScope] -> Value
$ctoJSONList :: [NotificationSettingsScope] -> Value
toEncoding :: NotificationSettingsScope -> Encoding
$ctoEncoding :: NotificationSettingsScope -> Encoding
toJSON :: NotificationSettingsScope -> Value
$ctoJSON :: NotificationSettingsScope -> Value
parseJSONList :: Value -> Parser [NotificationSettingsScope]
$cparseJSONList :: Value -> Parser [NotificationSettingsScope]
parseJSON :: Value -> Parser NotificationSettingsScope
$cparseJSON :: Value -> Parser NotificationSettingsScope
toEncodingList :: [ChatNotificationSettings] -> Encoding
$ctoEncodingList :: [ChatNotificationSettings] -> Encoding
toJSONList :: [ChatNotificationSettings] -> Value
$ctoJSONList :: [ChatNotificationSettings] -> Value
toEncoding :: ChatNotificationSettings -> Encoding
$ctoEncoding :: ChatNotificationSettings -> Encoding
toJSON :: ChatNotificationSettings -> Value
$ctoJSON :: ChatNotificationSettings -> Value
parseJSONList :: Value -> Parser [ChatNotificationSettings]
$cparseJSONList :: Value -> Parser [ChatNotificationSettings]
parseJSON :: Value -> Parser ChatNotificationSettings
$cparseJSON :: Value -> Parser ChatNotificationSettings
toEncodingList :: [ScopeNotificationSettings] -> Encoding
$ctoEncodingList :: [ScopeNotificationSettings] -> Encoding
toJSONList :: [ScopeNotificationSettings] -> Value
$ctoJSONList :: [ScopeNotificationSettings] -> Value
toEncoding :: ScopeNotificationSettings -> Encoding
$ctoEncoding :: ScopeNotificationSettings -> Encoding
toJSON :: ScopeNotificationSettings -> Value
$ctoJSON :: ScopeNotificationSettings -> Value
parseJSONList :: Value -> Parser [ScopeNotificationSettings]
$cparseJSONList :: Value -> Parser [ScopeNotificationSettings]
parseJSON :: Value -> Parser ScopeNotificationSettings
$cparseJSON :: Value -> Parser ScopeNotificationSettings
toEncodingList :: [DraftMessage] -> Encoding
$ctoEncodingList :: [DraftMessage] -> Encoding
toJSONList :: [DraftMessage] -> Value
$ctoJSONList :: [DraftMessage] -> Value
toEncoding :: DraftMessage -> Encoding
$ctoEncoding :: DraftMessage -> Encoding
toJSON :: DraftMessage -> Value
$ctoJSON :: DraftMessage -> Value
parseJSONList :: Value -> Parser [DraftMessage]
$cparseJSONList :: Value -> Parser [DraftMessage]
parseJSON :: Value -> Parser DraftMessage
$cparseJSON :: Value -> Parser DraftMessage
toEncodingList :: [ChatType] -> Encoding
$ctoEncodingList :: [ChatType] -> Encoding
toJSONList :: [ChatType] -> Value
$ctoJSONList :: [ChatType] -> Value
toEncoding :: ChatType -> Encoding
$ctoEncoding :: ChatType -> Encoding
toJSON :: ChatType -> Value
$ctoJSON :: ChatType -> Value
parseJSONList :: Value -> Parser [ChatType]
$cparseJSONList :: Value -> Parser [ChatType]
parseJSON :: Value -> Parser ChatType
$cparseJSON :: Value -> Parser ChatType
toEncodingList :: [ChatList] -> Encoding
$ctoEncodingList :: [ChatList] -> Encoding
toJSONList :: [ChatList] -> Value
$ctoJSONList :: [ChatList] -> Value
toEncoding :: ChatList -> Encoding
$ctoEncoding :: ChatList -> Encoding
toJSON :: ChatList -> Value
$ctoJSON :: ChatList -> Value
parseJSONList :: Value -> Parser [ChatList]
$cparseJSONList :: Value -> Parser [ChatList]
parseJSON :: Value -> Parser ChatList
$cparseJSON :: Value -> Parser ChatList
toEncodingList :: [ChatSource] -> Encoding
$ctoEncodingList :: [ChatSource] -> Encoding
toJSONList :: [ChatSource] -> Value
$ctoJSONList :: [ChatSource] -> Value
toEncoding :: ChatSource -> Encoding
$ctoEncoding :: ChatSource -> Encoding
toJSON :: ChatSource -> Value
$ctoJSON :: ChatSource -> Value
parseJSONList :: Value -> Parser [ChatSource]
$cparseJSONList :: Value -> Parser [ChatSource]
parseJSON :: Value -> Parser ChatSource
$cparseJSON :: Value -> Parser ChatSource
toEncodingList :: [Chat] -> Encoding
$ctoEncodingList :: [Chat] -> Encoding
toJSONList :: [Chat] -> Value
$ctoJSONList :: [Chat] -> Value
toEncoding :: Chat -> Encoding
$ctoEncoding :: Chat -> Encoding
toJSON :: Chat -> Value
$ctoJSON :: Chat -> Value
parseJSONList :: Value -> Parser [Chat]
$cparseJSONList :: Value -> Parser [Chat]
parseJSON :: Value -> Parser Chat
$cparseJSON :: Value -> Parser Chat
toEncodingList :: [Chats] -> Encoding
$ctoEncodingList :: [Chats] -> Encoding
toJSONList :: [Chats] -> Value
$ctoJSONList :: [Chats] -> Value
toEncoding :: Chats -> Encoding
$ctoEncoding :: Chats -> Encoding
toJSON :: Chats -> Value
$ctoJSON :: Chats -> Value
parseJSONList :: Value -> Parser [Chats]
$cparseJSONList :: Value -> Parser [Chats]
parseJSON :: Value -> Parser Chats
$cparseJSON :: Value -> Parser Chats
toEncodingList :: [ChatNearby] -> Encoding
$ctoEncodingList :: [ChatNearby] -> Encoding
toJSONList :: [ChatNearby] -> Value
$ctoJSONList :: [ChatNearby] -> Value
toEncoding :: ChatNearby -> Encoding
$ctoEncoding :: ChatNearby -> Encoding
toJSON :: ChatNearby -> Value
$ctoJSON :: ChatNearby -> Value
parseJSONList :: Value -> Parser [ChatNearby]
$cparseJSONList :: Value -> Parser [ChatNearby]
parseJSON :: Value -> Parser ChatNearby
$cparseJSON :: Value -> Parser ChatNearby
toEncodingList :: [ChatsNearby] -> Encoding
$ctoEncodingList :: [ChatsNearby] -> Encoding
toJSONList :: [ChatsNearby] -> Value
$ctoJSONList :: [ChatsNearby] -> Value
toEncoding :: ChatsNearby -> Encoding
$ctoEncoding :: ChatsNearby -> Encoding
toJSON :: ChatsNearby -> Value
$ctoJSON :: ChatsNearby -> Value
parseJSONList :: Value -> Parser [ChatsNearby]
$cparseJSONList :: Value -> Parser [ChatsNearby]
parseJSON :: Value -> Parser ChatsNearby
$cparseJSON :: Value -> Parser ChatsNearby
toEncodingList :: [ChatInviteLink] -> Encoding
$ctoEncodingList :: [ChatInviteLink] -> Encoding
toJSONList :: [ChatInviteLink] -> Value
$ctoJSONList :: [ChatInviteLink] -> Value
toEncoding :: ChatInviteLink -> Encoding
$ctoEncoding :: ChatInviteLink -> Encoding
toJSON :: ChatInviteLink -> Value
$ctoJSON :: ChatInviteLink -> Value
parseJSONList :: Value -> Parser [ChatInviteLink]
$cparseJSONList :: Value -> Parser [ChatInviteLink]
parseJSON :: Value -> Parser ChatInviteLink
$cparseJSON :: Value -> Parser ChatInviteLink
toEncodingList :: [ChatInviteLinkInfo] -> Encoding
$ctoEncodingList :: [ChatInviteLinkInfo] -> Encoding
toJSONList :: [ChatInviteLinkInfo] -> Value
$ctoJSONList :: [ChatInviteLinkInfo] -> Value
toEncoding :: ChatInviteLinkInfo -> Encoding
$ctoEncoding :: ChatInviteLinkInfo -> Encoding
toJSON :: ChatInviteLinkInfo -> Value
$ctoJSON :: ChatInviteLinkInfo -> Value
parseJSONList :: Value -> Parser [ChatInviteLinkInfo]
$cparseJSONList :: Value -> Parser [ChatInviteLinkInfo]
parseJSON :: Value -> Parser ChatInviteLinkInfo
$cparseJSON :: Value -> Parser ChatInviteLinkInfo
toEncodingList :: [PublicChatType] -> Encoding
$ctoEncodingList :: [PublicChatType] -> Encoding
toJSONList :: [PublicChatType] -> Value
$ctoJSONList :: [PublicChatType] -> Value
toEncoding :: PublicChatType -> Encoding
$ctoEncoding :: PublicChatType -> Encoding
toJSON :: PublicChatType -> Value
$ctoJSON :: PublicChatType -> Value
parseJSONList :: Value -> Parser [PublicChatType]
$cparseJSONList :: Value -> Parser [PublicChatType]
parseJSON :: Value -> Parser PublicChatType
$cparseJSON :: Value -> Parser PublicChatType
toEncodingList :: [ChatActionBar] -> Encoding
$ctoEncodingList :: [ChatActionBar] -> Encoding
toJSONList :: [ChatActionBar] -> Value
$ctoJSONList :: [ChatActionBar] -> Value
toEncoding :: ChatActionBar -> Encoding
$ctoEncoding :: ChatActionBar -> Encoding
toJSON :: ChatActionBar -> Value
$ctoJSON :: ChatActionBar -> Value
parseJSONList :: Value -> Parser [ChatActionBar]
$cparseJSONList :: Value -> Parser [ChatActionBar]
parseJSON :: Value -> Parser ChatActionBar
$cparseJSON :: Value -> Parser ChatActionBar
toEncodingList :: [KeyboardButtonType] -> Encoding
$ctoEncodingList :: [KeyboardButtonType] -> Encoding
toJSONList :: [KeyboardButtonType] -> Value
$ctoJSONList :: [KeyboardButtonType] -> Value
toEncoding :: KeyboardButtonType -> Encoding
$ctoEncoding :: KeyboardButtonType -> Encoding
toJSON :: KeyboardButtonType -> Value
$ctoJSON :: KeyboardButtonType -> Value
parseJSONList :: Value -> Parser [KeyboardButtonType]
$cparseJSONList :: Value -> Parser [KeyboardButtonType]
parseJSON :: Value -> Parser KeyboardButtonType
$cparseJSON :: Value -> Parser KeyboardButtonType
toEncodingList :: [KeyboardButton] -> Encoding
$ctoEncodingList :: [KeyboardButton] -> Encoding
toJSONList :: [KeyboardButton] -> Value
$ctoJSONList :: [KeyboardButton] -> Value
toEncoding :: KeyboardButton -> Encoding
$ctoEncoding :: KeyboardButton -> Encoding
toJSON :: KeyboardButton -> Value
$ctoJSON :: KeyboardButton -> Value
parseJSONList :: Value -> Parser [KeyboardButton]
$cparseJSONList :: Value -> Parser [KeyboardButton]
parseJSON :: Value -> Parser KeyboardButton
$cparseJSON :: Value -> Parser KeyboardButton
toEncodingList :: [InlineKeyboardButtonType] -> Encoding
$ctoEncodingList :: [InlineKeyboardButtonType] -> Encoding
toJSONList :: [InlineKeyboardButtonType] -> Value
$ctoJSONList :: [InlineKeyboardButtonType] -> Value
toEncoding :: InlineKeyboardButtonType -> Encoding
$ctoEncoding :: InlineKeyboardButtonType -> Encoding
toJSON :: InlineKeyboardButtonType -> Value
$ctoJSON :: InlineKeyboardButtonType -> Value
parseJSONList :: Value -> Parser [InlineKeyboardButtonType]
$cparseJSONList :: Value -> Parser [InlineKeyboardButtonType]
parseJSON :: Value -> Parser InlineKeyboardButtonType
$cparseJSON :: Value -> Parser InlineKeyboardButtonType
toEncodingList :: [InlineKeyboardButton] -> Encoding
$ctoEncodingList :: [InlineKeyboardButton] -> Encoding
toJSONList :: [InlineKeyboardButton] -> Value
$ctoJSONList :: [InlineKeyboardButton] -> Value
toEncoding :: InlineKeyboardButton -> Encoding
$ctoEncoding :: InlineKeyboardButton -> Encoding
toJSON :: InlineKeyboardButton -> Value
$ctoJSON :: InlineKeyboardButton -> Value
parseJSONList :: Value -> Parser [InlineKeyboardButton]
$cparseJSONList :: Value -> Parser [InlineKeyboardButton]
parseJSON :: Value -> Parser InlineKeyboardButton
$cparseJSON :: Value -> Parser InlineKeyboardButton
toEncodingList :: [ReplyMarkup] -> Encoding
$ctoEncodingList :: [ReplyMarkup] -> Encoding
toJSONList :: [ReplyMarkup] -> Value
$ctoJSONList :: [ReplyMarkup] -> Value
toEncoding :: ReplyMarkup -> Encoding
$ctoEncoding :: ReplyMarkup -> Encoding
toJSON :: ReplyMarkup -> Value
$ctoJSON :: ReplyMarkup -> Value
parseJSONList :: Value -> Parser [ReplyMarkup]
$cparseJSONList :: Value -> Parser [ReplyMarkup]
parseJSON :: Value -> Parser ReplyMarkup
$cparseJSON :: Value -> Parser ReplyMarkup
toEncodingList :: [LoginUrlInfo] -> Encoding
$ctoEncodingList :: [LoginUrlInfo] -> Encoding
toJSONList :: [LoginUrlInfo] -> Value
$ctoJSONList :: [LoginUrlInfo] -> Value
toEncoding :: LoginUrlInfo -> Encoding
$ctoEncoding :: LoginUrlInfo -> Encoding
toJSON :: LoginUrlInfo -> Value
$ctoJSON :: LoginUrlInfo -> Value
parseJSONList :: Value -> Parser [LoginUrlInfo]
$cparseJSONList :: Value -> Parser [LoginUrlInfo]
parseJSON :: Value -> Parser LoginUrlInfo
$cparseJSON :: Value -> Parser LoginUrlInfo
toEncodingList :: [RichText] -> Encoding
$ctoEncodingList :: [RichText] -> Encoding
toJSONList :: [RichText] -> Value
$ctoJSONList :: [RichText] -> Value
toEncoding :: RichText -> Encoding
$ctoEncoding :: RichText -> Encoding
toJSON :: RichText -> Value
$ctoJSON :: RichText -> Value
parseJSONList :: Value -> Parser [RichText]
$cparseJSONList :: Value -> Parser [RichText]
parseJSON :: Value -> Parser RichText
$cparseJSON :: Value -> Parser RichText
toEncodingList :: [PageBlockCaption] -> Encoding
$ctoEncodingList :: [PageBlockCaption] -> Encoding
toJSONList :: [PageBlockCaption] -> Value
$ctoJSONList :: [PageBlockCaption] -> Value
toEncoding :: PageBlockCaption -> Encoding
$ctoEncoding :: PageBlockCaption -> Encoding
toJSON :: PageBlockCaption -> Value
$ctoJSON :: PageBlockCaption -> Value
parseJSONList :: Value -> Parser [PageBlockCaption]
$cparseJSONList :: Value -> Parser [PageBlockCaption]
parseJSON :: Value -> Parser PageBlockCaption
$cparseJSON :: Value -> Parser PageBlockCaption
toEncodingList :: [PageBlockListItem] -> Encoding
$ctoEncodingList :: [PageBlockListItem] -> Encoding
toJSONList :: [PageBlockListItem] -> Value
$ctoJSONList :: [PageBlockListItem] -> Value
toEncoding :: PageBlockListItem -> Encoding
$ctoEncoding :: PageBlockListItem -> Encoding
toJSON :: PageBlockListItem -> Value
$ctoJSON :: PageBlockListItem -> Value
parseJSONList :: Value -> Parser [PageBlockListItem]
$cparseJSONList :: Value -> Parser [PageBlockListItem]
parseJSON :: Value -> Parser PageBlockListItem
$cparseJSON :: Value -> Parser PageBlockListItem
toEncodingList :: [PageBlockHorizontalAlignment] -> Encoding
$ctoEncodingList :: [PageBlockHorizontalAlignment] -> Encoding
toJSONList :: [PageBlockHorizontalAlignment] -> Value
$ctoJSONList :: [PageBlockHorizontalAlignment] -> Value
toEncoding :: PageBlockHorizontalAlignment -> Encoding
$ctoEncoding :: PageBlockHorizontalAlignment -> Encoding
toJSON :: PageBlockHorizontalAlignment -> Value
$ctoJSON :: PageBlockHorizontalAlignment -> Value
parseJSONList :: Value -> Parser [PageBlockHorizontalAlignment]
$cparseJSONList :: Value -> Parser [PageBlockHorizontalAlignment]
parseJSON :: Value -> Parser PageBlockHorizontalAlignment
$cparseJSON :: Value -> Parser PageBlockHorizontalAlignment
toEncodingList :: [PageBlockVerticalAlignment] -> Encoding
$ctoEncodingList :: [PageBlockVerticalAlignment] -> Encoding
toJSONList :: [PageBlockVerticalAlignment] -> Value
$ctoJSONList :: [PageBlockVerticalAlignment] -> Value
toEncoding :: PageBlockVerticalAlignment -> Encoding
$ctoEncoding :: PageBlockVerticalAlignment -> Encoding
toJSON :: PageBlockVerticalAlignment -> Value
$ctoJSON :: PageBlockVerticalAlignment -> Value
parseJSONList :: Value -> Parser [PageBlockVerticalAlignment]
$cparseJSONList :: Value -> Parser [PageBlockVerticalAlignment]
parseJSON :: Value -> Parser PageBlockVerticalAlignment
$cparseJSON :: Value -> Parser PageBlockVerticalAlignment
toEncodingList :: [PageBlockTableCell] -> Encoding
$ctoEncodingList :: [PageBlockTableCell] -> Encoding
toJSONList :: [PageBlockTableCell] -> Value
$ctoJSONList :: [PageBlockTableCell] -> Value
toEncoding :: PageBlockTableCell -> Encoding
$ctoEncoding :: PageBlockTableCell -> Encoding
toJSON :: PageBlockTableCell -> Value
$ctoJSON :: PageBlockTableCell -> Value
parseJSONList :: Value -> Parser [PageBlockTableCell]
$cparseJSONList :: Value -> Parser [PageBlockTableCell]
parseJSON :: Value -> Parser PageBlockTableCell
$cparseJSON :: Value -> Parser PageBlockTableCell
toEncodingList :: [PageBlockRelatedArticle] -> Encoding
$ctoEncodingList :: [PageBlockRelatedArticle] -> Encoding
toJSONList :: [PageBlockRelatedArticle] -> Value
$ctoJSONList :: [PageBlockRelatedArticle] -> Value
toEncoding :: PageBlockRelatedArticle -> Encoding
$ctoEncoding :: PageBlockRelatedArticle -> Encoding
toJSON :: PageBlockRelatedArticle -> Value
$ctoJSON :: PageBlockRelatedArticle -> Value
parseJSONList :: Value -> Parser [PageBlockRelatedArticle]
$cparseJSONList :: Value -> Parser [PageBlockRelatedArticle]
parseJSON :: Value -> Parser PageBlockRelatedArticle
$cparseJSON :: Value -> Parser PageBlockRelatedArticle
toEncodingList :: [PageBlock] -> Encoding
$ctoEncodingList :: [PageBlock] -> Encoding
toJSONList :: [PageBlock] -> Value
$ctoJSONList :: [PageBlock] -> Value
toEncoding :: PageBlock -> Encoding
$ctoEncoding :: PageBlock -> Encoding
toJSON :: PageBlock -> Value
$ctoJSON :: PageBlock -> Value
parseJSONList :: Value -> Parser [PageBlock]
$cparseJSONList :: Value -> Parser [PageBlock]
parseJSON :: Value -> Parser PageBlock
$cparseJSON :: Value -> Parser PageBlock
toEncodingList :: [WebPageInstantView] -> Encoding
$ctoEncodingList :: [WebPageInstantView] -> Encoding
toJSONList :: [WebPageInstantView] -> Value
$ctoJSONList :: [WebPageInstantView] -> Value
toEncoding :: WebPageInstantView -> Encoding
$ctoEncoding :: WebPageInstantView -> Encoding
toJSON :: WebPageInstantView -> Value
$ctoJSON :: WebPageInstantView -> Value
parseJSONList :: Value -> Parser [WebPageInstantView]
$cparseJSONList :: Value -> Parser [WebPageInstantView]
parseJSON :: Value -> Parser WebPageInstantView
$cparseJSON :: Value -> Parser WebPageInstantView
toEncodingList :: [WebPage] -> Encoding
$ctoEncodingList :: [WebPage] -> Encoding
toJSONList :: [WebPage] -> Value
$ctoJSONList :: [WebPage] -> Value
toEncoding :: WebPage -> Encoding
$ctoEncoding :: WebPage -> Encoding
toJSON :: WebPage -> Value
$ctoJSON :: WebPage -> Value
parseJSONList :: Value -> Parser [WebPage]
$cparseJSONList :: Value -> Parser [WebPage]
parseJSON :: Value -> Parser WebPage
$cparseJSON :: Value -> Parser WebPage
toEncodingList :: [BankCardActionOpenUrl] -> Encoding
$ctoEncodingList :: [BankCardActionOpenUrl] -> Encoding
toJSONList :: [BankCardActionOpenUrl] -> Value
$ctoJSONList :: [BankCardActionOpenUrl] -> Value
toEncoding :: BankCardActionOpenUrl -> Encoding
$ctoEncoding :: BankCardActionOpenUrl -> Encoding
toJSON :: BankCardActionOpenUrl -> Value
$ctoJSON :: BankCardActionOpenUrl -> Value
parseJSONList :: Value -> Parser [BankCardActionOpenUrl]
$cparseJSONList :: Value -> Parser [BankCardActionOpenUrl]
parseJSON :: Value -> Parser BankCardActionOpenUrl
$cparseJSON :: Value -> Parser BankCardActionOpenUrl
toEncodingList :: [BankCardInfo] -> Encoding
$ctoEncodingList :: [BankCardInfo] -> Encoding
toJSONList :: [BankCardInfo] -> Value
$ctoJSONList :: [BankCardInfo] -> Value
toEncoding :: BankCardInfo -> Encoding
$ctoEncoding :: BankCardInfo -> Encoding
toJSON :: BankCardInfo -> Value
$ctoJSON :: BankCardInfo -> Value
parseJSONList :: Value -> Parser [BankCardInfo]
$cparseJSONList :: Value -> Parser [BankCardInfo]
parseJSON :: Value -> Parser BankCardInfo
$cparseJSON :: Value -> Parser BankCardInfo
toEncodingList :: [Address] -> Encoding
$ctoEncodingList :: [Address] -> Encoding
toJSONList :: [Address] -> Value
$ctoJSONList :: [Address] -> Value
toEncoding :: Address -> Encoding
$ctoEncoding :: Address -> Encoding
toJSON :: Address -> Value
$ctoJSON :: Address -> Value
parseJSONList :: Value -> Parser [Address]
$cparseJSONList :: Value -> Parser [Address]
parseJSON :: Value -> Parser Address
$cparseJSON :: Value -> Parser Address
toEncodingList :: [LabeledPricePart] -> Encoding
$ctoEncodingList :: [LabeledPricePart] -> Encoding
toJSONList :: [LabeledPricePart] -> Value
$ctoJSONList :: [LabeledPricePart] -> Value
toEncoding :: LabeledPricePart -> Encoding
$ctoEncoding :: LabeledPricePart -> Encoding
toJSON :: LabeledPricePart -> Value
$ctoJSON :: LabeledPricePart -> Value
parseJSONList :: Value -> Parser [LabeledPricePart]
$cparseJSONList :: Value -> Parser [LabeledPricePart]
parseJSON :: Value -> Parser LabeledPricePart
$cparseJSON :: Value -> Parser LabeledPricePart
toEncodingList :: [Invoice] -> Encoding
$ctoEncodingList :: [Invoice] -> Encoding
toJSONList :: [Invoice] -> Value
$ctoJSONList :: [Invoice] -> Value
toEncoding :: Invoice -> Encoding
$ctoEncoding :: Invoice -> Encoding
toJSON :: Invoice -> Value
$ctoJSON :: Invoice -> Value
parseJSONList :: Value -> Parser [Invoice]
$cparseJSONList :: Value -> Parser [Invoice]
parseJSON :: Value -> Parser Invoice
$cparseJSON :: Value -> Parser Invoice
toEncodingList :: [OrderInfo] -> Encoding
$ctoEncodingList :: [OrderInfo] -> Encoding
toJSONList :: [OrderInfo] -> Value
$ctoJSONList :: [OrderInfo] -> Value
toEncoding :: OrderInfo -> Encoding
$ctoEncoding :: OrderInfo -> Encoding
toJSON :: OrderInfo -> Value
$ctoJSON :: OrderInfo -> Value
parseJSONList :: Value -> Parser [OrderInfo]
$cparseJSONList :: Value -> Parser [OrderInfo]
parseJSON :: Value -> Parser OrderInfo
$cparseJSON :: Value -> Parser OrderInfo
toEncodingList :: [ShippingOption] -> Encoding
$ctoEncodingList :: [ShippingOption] -> Encoding
toJSONList :: [ShippingOption] -> Value
$ctoJSONList :: [ShippingOption] -> Value
toEncoding :: ShippingOption -> Encoding
$ctoEncoding :: ShippingOption -> Encoding
toJSON :: ShippingOption -> Value
$ctoJSON :: ShippingOption -> Value
parseJSONList :: Value -> Parser [ShippingOption]
$cparseJSONList :: Value -> Parser [ShippingOption]
parseJSON :: Value -> Parser ShippingOption
$cparseJSON :: Value -> Parser ShippingOption
toEncodingList :: [SavedCredentials] -> Encoding
$ctoEncodingList :: [SavedCredentials] -> Encoding
toJSONList :: [SavedCredentials] -> Value
$ctoJSONList :: [SavedCredentials] -> Value
toEncoding :: SavedCredentials -> Encoding
$ctoEncoding :: SavedCredentials -> Encoding
toJSON :: SavedCredentials -> Value
$ctoJSON :: SavedCredentials -> Value
parseJSONList :: Value -> Parser [SavedCredentials]
$cparseJSONList :: Value -> Parser [SavedCredentials]
parseJSON :: Value -> Parser SavedCredentials
$cparseJSON :: Value -> Parser SavedCredentials
toEncodingList :: [InputCredentials] -> Encoding
$ctoEncodingList :: [InputCredentials] -> Encoding
toJSONList :: [InputCredentials] -> Value
$ctoJSONList :: [InputCredentials] -> Value
toEncoding :: InputCredentials -> Encoding
$ctoEncoding :: InputCredentials -> Encoding
toJSON :: InputCredentials -> Value
$ctoJSON :: InputCredentials -> Value
parseJSONList :: Value -> Parser [InputCredentials]
$cparseJSONList :: Value -> Parser [InputCredentials]
parseJSON :: Value -> Parser InputCredentials
$cparseJSON :: Value -> Parser InputCredentials
toEncodingList :: [PaymentsProviderStripe] -> Encoding
$ctoEncodingList :: [PaymentsProviderStripe] -> Encoding
toJSONList :: [PaymentsProviderStripe] -> Value
$ctoJSONList :: [PaymentsProviderStripe] -> Value
toEncoding :: PaymentsProviderStripe -> Encoding
$ctoEncoding :: PaymentsProviderStripe -> Encoding
toJSON :: PaymentsProviderStripe -> Value
$ctoJSON :: PaymentsProviderStripe -> Value
parseJSONList :: Value -> Parser [PaymentsProviderStripe]
$cparseJSONList :: Value -> Parser [PaymentsProviderStripe]
parseJSON :: Value -> Parser PaymentsProviderStripe
$cparseJSON :: Value -> Parser PaymentsProviderStripe
toEncodingList :: [PaymentForm] -> Encoding
$ctoEncodingList :: [PaymentForm] -> Encoding
toJSONList :: [PaymentForm] -> Value
$ctoJSONList :: [PaymentForm] -> Value
toEncoding :: PaymentForm -> Encoding
$ctoEncoding :: PaymentForm -> Encoding
toJSON :: PaymentForm -> Value
$ctoJSON :: PaymentForm -> Value
parseJSONList :: Value -> Parser [PaymentForm]
$cparseJSONList :: Value -> Parser [PaymentForm]
parseJSON :: Value -> Parser PaymentForm
$cparseJSON :: Value -> Parser PaymentForm
toEncodingList :: [ValidatedOrderInfo] -> Encoding
$ctoEncodingList :: [ValidatedOrderInfo] -> Encoding
toJSONList :: [ValidatedOrderInfo] -> Value
$ctoJSONList :: [ValidatedOrderInfo] -> Value
toEncoding :: ValidatedOrderInfo -> Encoding
$ctoEncoding :: ValidatedOrderInfo -> Encoding
toJSON :: ValidatedOrderInfo -> Value
$ctoJSON :: ValidatedOrderInfo -> Value
parseJSONList :: Value -> Parser [ValidatedOrderInfo]
$cparseJSONList :: Value -> Parser [ValidatedOrderInfo]
parseJSON :: Value -> Parser ValidatedOrderInfo
$cparseJSON :: Value -> Parser ValidatedOrderInfo
toEncodingList :: [PaymentResult] -> Encoding
$ctoEncodingList :: [PaymentResult] -> Encoding
toJSONList :: [PaymentResult] -> Value
$ctoJSONList :: [PaymentResult] -> Value
toEncoding :: PaymentResult -> Encoding
$ctoEncoding :: PaymentResult -> Encoding
toJSON :: PaymentResult -> Value
$ctoJSON :: PaymentResult -> Value
parseJSONList :: Value -> Parser [PaymentResult]
$cparseJSONList :: Value -> Parser [PaymentResult]
parseJSON :: Value -> Parser PaymentResult
$cparseJSON :: Value -> Parser PaymentResult
toEncodingList :: [PaymentReceipt] -> Encoding
$ctoEncodingList :: [PaymentReceipt] -> Encoding
toJSONList :: [PaymentReceipt] -> Value
$ctoJSONList :: [PaymentReceipt] -> Value
toEncoding :: PaymentReceipt -> Encoding
$ctoEncoding :: PaymentReceipt -> Encoding
toJSON :: PaymentReceipt -> Value
$ctoJSON :: PaymentReceipt -> Value
parseJSONList :: Value -> Parser [PaymentReceipt]
$cparseJSONList :: Value -> Parser [PaymentReceipt]
parseJSON :: Value -> Parser PaymentReceipt
$cparseJSON :: Value -> Parser PaymentReceipt
toEncodingList :: [DatedFile] -> Encoding
$ctoEncodingList :: [DatedFile] -> Encoding
toJSONList :: [DatedFile] -> Value
$ctoJSONList :: [DatedFile] -> Value
toEncoding :: DatedFile -> Encoding
$ctoEncoding :: DatedFile -> Encoding
toJSON :: DatedFile -> Value
$ctoJSON :: DatedFile -> Value
parseJSONList :: Value -> Parser [DatedFile]
$cparseJSONList :: Value -> Parser [DatedFile]
parseJSON :: Value -> Parser DatedFile
$cparseJSON :: Value -> Parser DatedFile
toEncodingList :: [PassportElementType] -> Encoding
$ctoEncodingList :: [PassportElementType] -> Encoding
toJSONList :: [PassportElementType] -> Value
$ctoJSONList :: [PassportElementType] -> Value
toEncoding :: PassportElementType -> Encoding
$ctoEncoding :: PassportElementType -> Encoding
toJSON :: PassportElementType -> Value
$ctoJSON :: PassportElementType -> Value
parseJSONList :: Value -> Parser [PassportElementType]
$cparseJSONList :: Value -> Parser [PassportElementType]
parseJSON :: Value -> Parser PassportElementType
$cparseJSON :: Value -> Parser PassportElementType
toEncodingList :: [Date] -> Encoding
$ctoEncodingList :: [Date] -> Encoding
toJSONList :: [Date] -> Value
$ctoJSONList :: [Date] -> Value
toEncoding :: Date -> Encoding
$ctoEncoding :: Date -> Encoding
toJSON :: Date -> Value
$ctoJSON :: Date -> Value
parseJSONList :: Value -> Parser [Date]
$cparseJSONList :: Value -> Parser [Date]
parseJSON :: Value -> Parser Date
$cparseJSON :: Value -> Parser Date
toEncodingList :: [PersonalDetails] -> Encoding
$ctoEncodingList :: [PersonalDetails] -> Encoding
toJSONList :: [PersonalDetails] -> Value
$ctoJSONList :: [PersonalDetails] -> Value
toEncoding :: PersonalDetails -> Encoding
$ctoEncoding :: PersonalDetails -> Encoding
toJSON :: PersonalDetails -> Value
$ctoJSON :: PersonalDetails -> Value
parseJSONList :: Value -> Parser [PersonalDetails]
$cparseJSONList :: Value -> Parser [PersonalDetails]
parseJSON :: Value -> Parser PersonalDetails
$cparseJSON :: Value -> Parser PersonalDetails
toEncodingList :: [IdentityDocument] -> Encoding
$ctoEncodingList :: [IdentityDocument] -> Encoding
toJSONList :: [IdentityDocument] -> Value
$ctoJSONList :: [IdentityDocument] -> Value
toEncoding :: IdentityDocument -> Encoding
$ctoEncoding :: IdentityDocument -> Encoding
toJSON :: IdentityDocument -> Value
$ctoJSON :: IdentityDocument -> Value
parseJSONList :: Value -> Parser [IdentityDocument]
$cparseJSONList :: Value -> Parser [IdentityDocument]
parseJSON :: Value -> Parser IdentityDocument
$cparseJSON :: Value -> Parser IdentityDocument
toEncodingList :: [InputIdentityDocument] -> Encoding
$ctoEncodingList :: [InputIdentityDocument] -> Encoding
toJSONList :: [InputIdentityDocument] -> Value
$ctoJSONList :: [InputIdentityDocument] -> Value
toEncoding :: InputIdentityDocument -> Encoding
$ctoEncoding :: InputIdentityDocument -> Encoding
toJSON :: InputIdentityDocument -> Value
$ctoJSON :: InputIdentityDocument -> Value
parseJSONList :: Value -> Parser [InputIdentityDocument]
$cparseJSONList :: Value -> Parser [InputIdentityDocument]
parseJSON :: Value -> Parser InputIdentityDocument
$cparseJSON :: Value -> Parser InputIdentityDocument
toEncodingList :: [PersonalDocument] -> Encoding
$ctoEncodingList :: [PersonalDocument] -> Encoding
toJSONList :: [PersonalDocument] -> Value
$ctoJSONList :: [PersonalDocument] -> Value
toEncoding :: PersonalDocument -> Encoding
$ctoEncoding :: PersonalDocument -> Encoding
toJSON :: PersonalDocument -> Value
$ctoJSON :: PersonalDocument -> Value
parseJSONList :: Value -> Parser [PersonalDocument]
$cparseJSONList :: Value -> Parser [PersonalDocument]
parseJSON :: Value -> Parser PersonalDocument
$cparseJSON :: Value -> Parser PersonalDocument
toEncodingList :: [InputPersonalDocument] -> Encoding
$ctoEncodingList :: [InputPersonalDocument] -> Encoding
toJSONList :: [InputPersonalDocument] -> Value
$ctoJSONList :: [InputPersonalDocument] -> Value
toEncoding :: InputPersonalDocument -> Encoding
$ctoEncoding :: InputPersonalDocument -> Encoding
toJSON :: InputPersonalDocument -> Value
$ctoJSON :: InputPersonalDocument -> Value
parseJSONList :: Value -> Parser [InputPersonalDocument]
$cparseJSONList :: Value -> Parser [InputPersonalDocument]
parseJSON :: Value -> Parser InputPersonalDocument
$cparseJSON :: Value -> Parser InputPersonalDocument
toEncodingList :: [PassportElement] -> Encoding
$ctoEncodingList :: [PassportElement] -> Encoding
toJSONList :: [PassportElement] -> Value
$ctoJSONList :: [PassportElement] -> Value
toEncoding :: PassportElement -> Encoding
$ctoEncoding :: PassportElement -> Encoding
toJSON :: PassportElement -> Value
$ctoJSON :: PassportElement -> Value
parseJSONList :: Value -> Parser [PassportElement]
$cparseJSONList :: Value -> Parser [PassportElement]
parseJSON :: Value -> Parser PassportElement
$cparseJSON :: Value -> Parser PassportElement
toEncodingList :: [InputPassportElement] -> Encoding
$ctoEncodingList :: [InputPassportElement] -> Encoding
toJSONList :: [InputPassportElement] -> Value
$ctoJSONList :: [InputPassportElement] -> Value
toEncoding :: InputPassportElement -> Encoding
$ctoEncoding :: InputPassportElement -> Encoding
toJSON :: InputPassportElement -> Value
$ctoJSON :: InputPassportElement -> Value
parseJSONList :: Value -> Parser [InputPassportElement]
$cparseJSONList :: Value -> Parser [InputPassportElement]
parseJSON :: Value -> Parser InputPassportElement
$cparseJSON :: Value -> Parser InputPassportElement
toEncodingList :: [PassportElements] -> Encoding
$ctoEncodingList :: [PassportElements] -> Encoding
toJSONList :: [PassportElements] -> Value
$ctoJSONList :: [PassportElements] -> Value
toEncoding :: PassportElements -> Encoding
$ctoEncoding :: PassportElements -> Encoding
toJSON :: PassportElements -> Value
$ctoJSON :: PassportElements -> Value
parseJSONList :: Value -> Parser [PassportElements]
$cparseJSONList :: Value -> Parser [PassportElements]
parseJSON :: Value -> Parser PassportElements
$cparseJSON :: Value -> Parser PassportElements
toEncodingList :: [PassportElementErrorSource] -> Encoding
$ctoEncodingList :: [PassportElementErrorSource] -> Encoding
toJSONList :: [PassportElementErrorSource] -> Value
$ctoJSONList :: [PassportElementErrorSource] -> Value
toEncoding :: PassportElementErrorSource -> Encoding
$ctoEncoding :: PassportElementErrorSource -> Encoding
toJSON :: PassportElementErrorSource -> Value
$ctoJSON :: PassportElementErrorSource -> Value
parseJSONList :: Value -> Parser [PassportElementErrorSource]
$cparseJSONList :: Value -> Parser [PassportElementErrorSource]
parseJSON :: Value -> Parser PassportElementErrorSource
$cparseJSON :: Value -> Parser PassportElementErrorSource
toEncodingList :: [PassportElementError] -> Encoding
$ctoEncodingList :: [PassportElementError] -> Encoding
toJSONList :: [PassportElementError] -> Value
$ctoJSONList :: [PassportElementError] -> Value
toEncoding :: PassportElementError -> Encoding
$ctoEncoding :: PassportElementError -> Encoding
toJSON :: PassportElementError -> Value
$ctoJSON :: PassportElementError -> Value
parseJSONList :: Value -> Parser [PassportElementError]
$cparseJSONList :: Value -> Parser [PassportElementError]
parseJSON :: Value -> Parser PassportElementError
$cparseJSON :: Value -> Parser PassportElementError
toEncodingList :: [PassportSuitableElement] -> Encoding
$ctoEncodingList :: [PassportSuitableElement] -> Encoding
toJSONList :: [PassportSuitableElement] -> Value
$ctoJSONList :: [PassportSuitableElement] -> Value
toEncoding :: PassportSuitableElement -> Encoding
$ctoEncoding :: PassportSuitableElement -> Encoding
toJSON :: PassportSuitableElement -> Value
$ctoJSON :: PassportSuitableElement -> Value
parseJSONList :: Value -> Parser [PassportSuitableElement]
$cparseJSONList :: Value -> Parser [PassportSuitableElement]
parseJSON :: Value -> Parser PassportSuitableElement
$cparseJSON :: Value -> Parser PassportSuitableElement
toEncodingList :: [PassportRequiredElement] -> Encoding
$ctoEncodingList :: [PassportRequiredElement] -> Encoding
toJSONList :: [PassportRequiredElement] -> Value
$ctoJSONList :: [PassportRequiredElement] -> Value
toEncoding :: PassportRequiredElement -> Encoding
$ctoEncoding :: PassportRequiredElement -> Encoding
toJSON :: PassportRequiredElement -> Value
$ctoJSON :: PassportRequiredElement -> Value
parseJSONList :: Value -> Parser [PassportRequiredElement]
$cparseJSONList :: Value -> Parser [PassportRequiredElement]
parseJSON :: Value -> Parser PassportRequiredElement
$cparseJSON :: Value -> Parser PassportRequiredElement
toEncodingList :: [PassportAuthorizationForm] -> Encoding
$ctoEncodingList :: [PassportAuthorizationForm] -> Encoding
toJSONList :: [PassportAuthorizationForm] -> Value
$ctoJSONList :: [PassportAuthorizationForm] -> Value
toEncoding :: PassportAuthorizationForm -> Encoding
$ctoEncoding :: PassportAuthorizationForm -> Encoding
toJSON :: PassportAuthorizationForm -> Value
$ctoJSON :: PassportAuthorizationForm -> Value
parseJSONList :: Value -> Parser [PassportAuthorizationForm]
$cparseJSONList :: Value -> Parser [PassportAuthorizationForm]
parseJSON :: Value -> Parser PassportAuthorizationForm
$cparseJSON :: Value -> Parser PassportAuthorizationForm
toEncodingList :: [PassportElementsWithErrors] -> Encoding
$ctoEncodingList :: [PassportElementsWithErrors] -> Encoding
toJSONList :: [PassportElementsWithErrors] -> Value
$ctoJSONList :: [PassportElementsWithErrors] -> Value
toEncoding :: PassportElementsWithErrors -> Encoding
$ctoEncoding :: PassportElementsWithErrors -> Encoding
toJSON :: PassportElementsWithErrors -> Value
$ctoJSON :: PassportElementsWithErrors -> Value
parseJSONList :: Value -> Parser [PassportElementsWithErrors]
$cparseJSONList :: Value -> Parser [PassportElementsWithErrors]
parseJSON :: Value -> Parser PassportElementsWithErrors
$cparseJSON :: Value -> Parser PassportElementsWithErrors
toEncodingList :: [EncryptedCredentials] -> Encoding
$ctoEncodingList :: [EncryptedCredentials] -> Encoding
toJSONList :: [EncryptedCredentials] -> Value
$ctoJSONList :: [EncryptedCredentials] -> Value
toEncoding :: EncryptedCredentials -> Encoding
$ctoEncoding :: EncryptedCredentials -> Encoding
toJSON :: EncryptedCredentials -> Value
$ctoJSON :: EncryptedCredentials -> Value
parseJSONList :: Value -> Parser [EncryptedCredentials]
$cparseJSONList :: Value -> Parser [EncryptedCredentials]
parseJSON :: Value -> Parser EncryptedCredentials
$cparseJSON :: Value -> Parser EncryptedCredentials
toEncodingList :: [EncryptedPassportElement] -> Encoding
$ctoEncodingList :: [EncryptedPassportElement] -> Encoding
toJSONList :: [EncryptedPassportElement] -> Value
$ctoJSONList :: [EncryptedPassportElement] -> Value
toEncoding :: EncryptedPassportElement -> Encoding
$ctoEncoding :: EncryptedPassportElement -> Encoding
toJSON :: EncryptedPassportElement -> Value
$ctoJSON :: EncryptedPassportElement -> Value
parseJSONList :: Value -> Parser [EncryptedPassportElement]
$cparseJSONList :: Value -> Parser [EncryptedPassportElement]
parseJSON :: Value -> Parser EncryptedPassportElement
$cparseJSON :: Value -> Parser EncryptedPassportElement
toEncodingList :: [InputPassportElementErrorSource] -> Encoding
$ctoEncodingList :: [InputPassportElementErrorSource] -> Encoding
toJSONList :: [InputPassportElementErrorSource] -> Value
$ctoJSONList :: [InputPassportElementErrorSource] -> Value
toEncoding :: InputPassportElementErrorSource -> Encoding
$ctoEncoding :: InputPassportElementErrorSource -> Encoding
toJSON :: InputPassportElementErrorSource -> Value
$ctoJSON :: InputPassportElementErrorSource -> Value
parseJSONList :: Value -> Parser [InputPassportElementErrorSource]
$cparseJSONList :: Value -> Parser [InputPassportElementErrorSource]
parseJSON :: Value -> Parser InputPassportElementErrorSource
$cparseJSON :: Value -> Parser InputPassportElementErrorSource
toEncodingList :: [InputPassportElementError] -> Encoding
$ctoEncodingList :: [InputPassportElementError] -> Encoding
toJSONList :: [InputPassportElementError] -> Value
$ctoJSONList :: [InputPassportElementError] -> Value
toEncoding :: InputPassportElementError -> Encoding
$ctoEncoding :: InputPassportElementError -> Encoding
toJSON :: InputPassportElementError -> Value
$ctoJSON :: InputPassportElementError -> Value
parseJSONList :: Value -> Parser [InputPassportElementError]
$cparseJSONList :: Value -> Parser [InputPassportElementError]
parseJSON :: Value -> Parser InputPassportElementError
$cparseJSON :: Value -> Parser InputPassportElementError
toEncodingList :: [MessageContent] -> Encoding
$ctoEncodingList :: [MessageContent] -> Encoding
toJSONList :: [MessageContent] -> Value
$ctoJSONList :: [MessageContent] -> Value
toEncoding :: MessageContent -> Encoding
$ctoEncoding :: MessageContent -> Encoding
toJSON :: MessageContent -> Value
$ctoJSON :: MessageContent -> Value
parseJSONList :: Value -> Parser [MessageContent]
$cparseJSONList :: Value -> Parser [MessageContent]
parseJSON :: Value -> Parser MessageContent
$cparseJSON :: Value -> Parser MessageContent
toEncodingList :: [TextEntityType] -> Encoding
$ctoEncodingList :: [TextEntityType] -> Encoding
toJSONList :: [TextEntityType] -> Value
$ctoJSONList :: [TextEntityType] -> Value
toEncoding :: TextEntityType -> Encoding
$ctoEncoding :: TextEntityType -> Encoding
toJSON :: TextEntityType -> Value
$ctoJSON :: TextEntityType -> Value
parseJSONList :: Value -> Parser [TextEntityType]
$cparseJSONList :: Value -> Parser [TextEntityType]
parseJSON :: Value -> Parser TextEntityType
$cparseJSON :: Value -> Parser TextEntityType
toEncodingList :: [InputThumbnail] -> Encoding
$ctoEncodingList :: [InputThumbnail] -> Encoding
toJSONList :: [InputThumbnail] -> Value
$ctoJSONList :: [InputThumbnail] -> Value
toEncoding :: InputThumbnail -> Encoding
$ctoEncoding :: InputThumbnail -> Encoding
toJSON :: InputThumbnail -> Value
$ctoJSON :: InputThumbnail -> Value
parseJSONList :: Value -> Parser [InputThumbnail]
$cparseJSONList :: Value -> Parser [InputThumbnail]
parseJSON :: Value -> Parser InputThumbnail
$cparseJSON :: Value -> Parser InputThumbnail
toEncodingList :: [MessageSchedulingState] -> Encoding
$ctoEncodingList :: [MessageSchedulingState] -> Encoding
toJSONList :: [MessageSchedulingState] -> Value
$ctoJSONList :: [MessageSchedulingState] -> Value
toEncoding :: MessageSchedulingState -> Encoding
$ctoEncoding :: MessageSchedulingState -> Encoding
toJSON :: MessageSchedulingState -> Value
$ctoJSON :: MessageSchedulingState -> Value
parseJSONList :: Value -> Parser [MessageSchedulingState]
$cparseJSONList :: Value -> Parser [MessageSchedulingState]
parseJSON :: Value -> Parser MessageSchedulingState
$cparseJSON :: Value -> Parser MessageSchedulingState
toEncodingList :: [SendMessageOptions] -> Encoding
$ctoEncodingList :: [SendMessageOptions] -> Encoding
toJSONList :: [SendMessageOptions] -> Value
$ctoJSONList :: [SendMessageOptions] -> Value
toEncoding :: SendMessageOptions -> Encoding
$ctoEncoding :: SendMessageOptions -> Encoding
toJSON :: SendMessageOptions -> Value
$ctoJSON :: SendMessageOptions -> Value
parseJSONList :: Value -> Parser [SendMessageOptions]
$cparseJSONList :: Value -> Parser [SendMessageOptions]
parseJSON :: Value -> Parser SendMessageOptions
$cparseJSON :: Value -> Parser SendMessageOptions
toEncodingList :: [InputMessageContent] -> Encoding
$ctoEncodingList :: [InputMessageContent] -> Encoding
toJSONList :: [InputMessageContent] -> Value
$ctoJSONList :: [InputMessageContent] -> Value
toEncoding :: InputMessageContent -> Encoding
$ctoEncoding :: InputMessageContent -> Encoding
toJSON :: InputMessageContent -> Value
$ctoJSON :: InputMessageContent -> Value
parseJSONList :: Value -> Parser [InputMessageContent]
$cparseJSONList :: Value -> Parser [InputMessageContent]
parseJSON :: Value -> Parser InputMessageContent
$cparseJSON :: Value -> Parser InputMessageContent
toEncodingList :: [SearchMessagesFilter] -> Encoding
$ctoEncodingList :: [SearchMessagesFilter] -> Encoding
toJSONList :: [SearchMessagesFilter] -> Value
$ctoJSONList :: [SearchMessagesFilter] -> Value
toEncoding :: SearchMessagesFilter -> Encoding
$ctoEncoding :: SearchMessagesFilter -> Encoding
toJSON :: SearchMessagesFilter -> Value
$ctoJSON :: SearchMessagesFilter -> Value
parseJSONList :: Value -> Parser [SearchMessagesFilter]
$cparseJSONList :: Value -> Parser [SearchMessagesFilter]
parseJSON :: Value -> Parser SearchMessagesFilter
$cparseJSON :: Value -> Parser SearchMessagesFilter
toEncodingList :: [ChatAction] -> Encoding
$ctoEncodingList :: [ChatAction] -> Encoding
toJSONList :: [ChatAction] -> Value
$ctoJSONList :: [ChatAction] -> Value
toEncoding :: ChatAction -> Encoding
$ctoEncoding :: ChatAction -> Encoding
toJSON :: ChatAction -> Value
$ctoJSON :: ChatAction -> Value
parseJSONList :: Value -> Parser [ChatAction]
$cparseJSONList :: Value -> Parser [ChatAction]
parseJSON :: Value -> Parser ChatAction
$cparseJSON :: Value -> Parser ChatAction
toEncodingList :: [UserStatus] -> Encoding
$ctoEncodingList :: [UserStatus] -> Encoding
toJSONList :: [UserStatus] -> Value
$ctoJSONList :: [UserStatus] -> Value
toEncoding :: UserStatus -> Encoding
$ctoEncoding :: UserStatus -> Encoding
toJSON :: UserStatus -> Value
$ctoJSON :: UserStatus -> Value
parseJSONList :: Value -> Parser [UserStatus]
$cparseJSONList :: Value -> Parser [UserStatus]
parseJSON :: Value -> Parser UserStatus
$cparseJSON :: Value -> Parser UserStatus
toEncodingList :: [Stickers] -> Encoding
$ctoEncodingList :: [Stickers] -> Encoding
toJSONList :: [Stickers] -> Value
$ctoJSONList :: [Stickers] -> Value
toEncoding :: Stickers -> Encoding
$ctoEncoding :: Stickers -> Encoding
toJSON :: Stickers -> Value
$ctoJSON :: Stickers -> Value
parseJSONList :: Value -> Parser [Stickers]
$cparseJSONList :: Value -> Parser [Stickers]
parseJSON :: Value -> Parser Stickers
$cparseJSON :: Value -> Parser Stickers
toEncodingList :: [Emojis] -> Encoding
$ctoEncodingList :: [Emojis] -> Encoding
toJSONList :: [Emojis] -> Value
$ctoJSONList :: [Emojis] -> Value
toEncoding :: Emojis -> Encoding
$ctoEncoding :: Emojis -> Encoding
toJSON :: Emojis -> Value
$ctoJSON :: Emojis -> Value
parseJSONList :: Value -> Parser [Emojis]
$cparseJSONList :: Value -> Parser [Emojis]
parseJSON :: Value -> Parser Emojis
$cparseJSON :: Value -> Parser Emojis
toEncodingList :: [StickerSet] -> Encoding
$ctoEncodingList :: [StickerSet] -> Encoding
toJSONList :: [StickerSet] -> Value
$ctoJSONList :: [StickerSet] -> Value
toEncoding :: StickerSet -> Encoding
$ctoEncoding :: StickerSet -> Encoding
toJSON :: StickerSet -> Value
$ctoJSON :: StickerSet -> Value
parseJSONList :: Value -> Parser [StickerSet]
$cparseJSONList :: Value -> Parser [StickerSet]
parseJSON :: Value -> Parser StickerSet
$cparseJSON :: Value -> Parser StickerSet
toEncodingList :: [StickerSetInfo] -> Encoding
$ctoEncodingList :: [StickerSetInfo] -> Encoding
toJSONList :: [StickerSetInfo] -> Value
$ctoJSONList :: [StickerSetInfo] -> Value
toEncoding :: StickerSetInfo -> Encoding
$ctoEncoding :: StickerSetInfo -> Encoding
toJSON :: StickerSetInfo -> Value
$ctoJSON :: StickerSetInfo -> Value
parseJSONList :: Value -> Parser [StickerSetInfo]
$cparseJSONList :: Value -> Parser [StickerSetInfo]
parseJSON :: Value -> Parser StickerSetInfo
$cparseJSON :: Value -> Parser StickerSetInfo
toEncodingList :: [StickerSets] -> Encoding
$ctoEncodingList :: [StickerSets] -> Encoding
toJSONList :: [StickerSets] -> Value
$ctoJSONList :: [StickerSets] -> Value
toEncoding :: StickerSets -> Encoding
$ctoEncoding :: StickerSets -> Encoding
toJSON :: StickerSets -> Value
$ctoJSON :: StickerSets -> Value
parseJSONList :: Value -> Parser [StickerSets]
$cparseJSONList :: Value -> Parser [StickerSets]
parseJSON :: Value -> Parser StickerSets
$cparseJSON :: Value -> Parser StickerSets
toEncodingList :: [CallDiscardReason] -> Encoding
$ctoEncodingList :: [CallDiscardReason] -> Encoding
toJSONList :: [CallDiscardReason] -> Value
$ctoJSONList :: [CallDiscardReason] -> Value
toEncoding :: CallDiscardReason -> Encoding
$ctoEncoding :: CallDiscardReason -> Encoding
toJSON :: CallDiscardReason -> Value
$ctoJSON :: CallDiscardReason -> Value
parseJSONList :: Value -> Parser [CallDiscardReason]
$cparseJSONList :: Value -> Parser [CallDiscardReason]
parseJSON :: Value -> Parser CallDiscardReason
$cparseJSON :: Value -> Parser CallDiscardReason
toEncodingList :: [CallProtocol] -> Encoding
$ctoEncodingList :: [CallProtocol] -> Encoding
toJSONList :: [CallProtocol] -> Value
$ctoJSONList :: [CallProtocol] -> Value
toEncoding :: CallProtocol -> Encoding
$ctoEncoding :: CallProtocol -> Encoding
toJSON :: CallProtocol -> Value
$ctoJSON :: CallProtocol -> Value
parseJSONList :: Value -> Parser [CallProtocol]
$cparseJSONList :: Value -> Parser [CallProtocol]
parseJSON :: Value -> Parser CallProtocol
$cparseJSON :: Value -> Parser CallProtocol
toEncodingList :: [CallConnection] -> Encoding
$ctoEncodingList :: [CallConnection] -> Encoding
toJSONList :: [CallConnection] -> Value
$ctoJSONList :: [CallConnection] -> Value
toEncoding :: CallConnection -> Encoding
$ctoEncoding :: CallConnection -> Encoding
toJSON :: CallConnection -> Value
$ctoJSON :: CallConnection -> Value
parseJSONList :: Value -> Parser [CallConnection]
$cparseJSONList :: Value -> Parser [CallConnection]
parseJSON :: Value -> Parser CallConnection
$cparseJSON :: Value -> Parser CallConnection
toEncodingList :: [CallId] -> Encoding
$ctoEncodingList :: [CallId] -> Encoding
toJSONList :: [CallId] -> Value
$ctoJSONList :: [CallId] -> Value
toEncoding :: CallId -> Encoding
$ctoEncoding :: CallId -> Encoding
toJSON :: CallId -> Value
$ctoJSON :: CallId -> Value
parseJSONList :: Value -> Parser [CallId]
$cparseJSONList :: Value -> Parser [CallId]
parseJSON :: Value -> Parser CallId
$cparseJSON :: Value -> Parser CallId
toEncodingList :: [CallState] -> Encoding
$ctoEncodingList :: [CallState] -> Encoding
toJSONList :: [CallState] -> Value
$ctoJSONList :: [CallState] -> Value
toEncoding :: CallState -> Encoding
$ctoEncoding :: CallState -> Encoding
toJSON :: CallState -> Value
$ctoJSON :: CallState -> Value
parseJSONList :: Value -> Parser [CallState]
$cparseJSONList :: Value -> Parser [CallState]
parseJSON :: Value -> Parser CallState
$cparseJSON :: Value -> Parser CallState
toEncodingList :: [CallProblem] -> Encoding
$ctoEncodingList :: [CallProblem] -> Encoding
toJSONList :: [CallProblem] -> Value
$ctoJSONList :: [CallProblem] -> Value
toEncoding :: CallProblem -> Encoding
$ctoEncoding :: CallProblem -> Encoding
toJSON :: CallProblem -> Value
$ctoJSON :: CallProblem -> Value
parseJSONList :: Value -> Parser [CallProblem]
$cparseJSONList :: Value -> Parser [CallProblem]
parseJSON :: Value -> Parser CallProblem
$cparseJSON :: Value -> Parser CallProblem
toEncodingList :: [Call] -> Encoding
$ctoEncodingList :: [Call] -> Encoding
toJSONList :: [Call] -> Value
$ctoJSONList :: [Call] -> Value
toEncoding :: Call -> Encoding
$ctoEncoding :: Call -> Encoding
toJSON :: Call -> Value
$ctoJSON :: Call -> Value
parseJSONList :: Value -> Parser [Call]
$cparseJSONList :: Value -> Parser [Call]
parseJSON :: Value -> Parser Call
$cparseJSON :: Value -> Parser Call
toEncodingList :: [PhoneNumberAuthenticationSettings] -> Encoding
$ctoEncodingList :: [PhoneNumberAuthenticationSettings] -> Encoding
toJSONList :: [PhoneNumberAuthenticationSettings] -> Value
$ctoJSONList :: [PhoneNumberAuthenticationSettings] -> Value
toEncoding :: PhoneNumberAuthenticationSettings -> Encoding
$ctoEncoding :: PhoneNumberAuthenticationSettings -> Encoding
toJSON :: PhoneNumberAuthenticationSettings -> Value
$ctoJSON :: PhoneNumberAuthenticationSettings -> Value
parseJSONList :: Value -> Parser [PhoneNumberAuthenticationSettings]
$cparseJSONList :: Value -> Parser [PhoneNumberAuthenticationSettings]
parseJSON :: Value -> Parser PhoneNumberAuthenticationSettings
$cparseJSON :: Value -> Parser PhoneNumberAuthenticationSettings
toEncodingList :: [Animations] -> Encoding
$ctoEncodingList :: [Animations] -> Encoding
toJSONList :: [Animations] -> Value
$ctoJSONList :: [Animations] -> Value
toEncoding :: Animations -> Encoding
$ctoEncoding :: Animations -> Encoding
toJSON :: Animations -> Value
$ctoJSON :: Animations -> Value
parseJSONList :: Value -> Parser [Animations]
$cparseJSONList :: Value -> Parser [Animations]
parseJSON :: Value -> Parser Animations
$cparseJSON :: Value -> Parser Animations
toEncodingList :: [ImportedContacts] -> Encoding
$ctoEncodingList :: [ImportedContacts] -> Encoding
toJSONList :: [ImportedContacts] -> Value
$ctoJSONList :: [ImportedContacts] -> Value
toEncoding :: ImportedContacts -> Encoding
$ctoEncoding :: ImportedContacts -> Encoding
toJSON :: ImportedContacts -> Value
$ctoJSON :: ImportedContacts -> Value
parseJSONList :: Value -> Parser [ImportedContacts]
$cparseJSONList :: Value -> Parser [ImportedContacts]
parseJSON :: Value -> Parser ImportedContacts
$cparseJSON :: Value -> Parser ImportedContacts
toEncodingList :: [HttpUrl] -> Encoding
$ctoEncodingList :: [HttpUrl] -> Encoding
toJSONList :: [HttpUrl] -> Value
$ctoJSONList :: [HttpUrl] -> Value
toEncoding :: HttpUrl -> Encoding
$ctoEncoding :: HttpUrl -> Encoding
toJSON :: HttpUrl -> Value
$ctoJSON :: HttpUrl -> Value
parseJSONList :: Value -> Parser [HttpUrl]
$cparseJSONList :: Value -> Parser [HttpUrl]
parseJSON :: Value -> Parser HttpUrl
$cparseJSON :: Value -> Parser HttpUrl
toEncodingList :: [InputInlineQueryResult] -> Encoding
$ctoEncodingList :: [InputInlineQueryResult] -> Encoding
toJSONList :: [InputInlineQueryResult] -> Value
$ctoJSONList :: [InputInlineQueryResult] -> Value
toEncoding :: InputInlineQueryResult -> Encoding
$ctoEncoding :: InputInlineQueryResult -> Encoding
toJSON :: InputInlineQueryResult -> Value
$ctoJSON :: InputInlineQueryResult -> Value
parseJSONList :: Value -> Parser [InputInlineQueryResult]
$cparseJSONList :: Value -> Parser [InputInlineQueryResult]
parseJSON :: Value -> Parser InputInlineQueryResult
$cparseJSON :: Value -> Parser InputInlineQueryResult
toEncodingList :: [InlineQueryResult] -> Encoding
$ctoEncodingList :: [InlineQueryResult] -> Encoding
toJSONList :: [InlineQueryResult] -> Value
$ctoJSONList :: [InlineQueryResult] -> Value
toEncoding :: InlineQueryResult -> Encoding
$ctoEncoding :: InlineQueryResult -> Encoding
toJSON :: InlineQueryResult -> Value
$ctoJSON :: InlineQueryResult -> Value
parseJSONList :: Value -> Parser [InlineQueryResult]
$cparseJSONList :: Value -> Parser [InlineQueryResult]
parseJSON :: Value -> Parser InlineQueryResult
$cparseJSON :: Value -> Parser InlineQueryResult
toEncodingList :: [InlineQueryResults] -> Encoding
$ctoEncodingList :: [InlineQueryResults] -> Encoding
toJSONList :: [InlineQueryResults] -> Value
$ctoJSONList :: [InlineQueryResults] -> Value
toEncoding :: InlineQueryResults -> Encoding
$ctoEncoding :: InlineQueryResults -> Encoding
toJSON :: InlineQueryResults -> Value
$ctoJSON :: InlineQueryResults -> Value
parseJSONList :: Value -> Parser [InlineQueryResults]
$cparseJSONList :: Value -> Parser [InlineQueryResults]
parseJSON :: Value -> Parser InlineQueryResults
$cparseJSON :: Value -> Parser InlineQueryResults
toEncodingList :: [CallbackQueryPayload] -> Encoding
$ctoEncodingList :: [CallbackQueryPayload] -> Encoding
toJSONList :: [CallbackQueryPayload] -> Value
$ctoJSONList :: [CallbackQueryPayload] -> Value
toEncoding :: CallbackQueryPayload -> Encoding
$ctoEncoding :: CallbackQueryPayload -> Encoding
toJSON :: CallbackQueryPayload -> Value
$ctoJSON :: CallbackQueryPayload -> Value
parseJSONList :: Value -> Parser [CallbackQueryPayload]
$cparseJSONList :: Value -> Parser [CallbackQueryPayload]
parseJSON :: Value -> Parser CallbackQueryPayload
$cparseJSON :: Value -> Parser CallbackQueryPayload
toEncodingList :: [CallbackQueryAnswer] -> Encoding
$ctoEncodingList :: [CallbackQueryAnswer] -> Encoding
toJSONList :: [CallbackQueryAnswer] -> Value
$ctoJSONList :: [CallbackQueryAnswer] -> Value
toEncoding :: CallbackQueryAnswer -> Encoding
$ctoEncoding :: CallbackQueryAnswer -> Encoding
toJSON :: CallbackQueryAnswer -> Value
$ctoJSON :: CallbackQueryAnswer -> Value
parseJSONList :: Value -> Parser [CallbackQueryAnswer]
$cparseJSONList :: Value -> Parser [CallbackQueryAnswer]
parseJSON :: Value -> Parser CallbackQueryAnswer
$cparseJSON :: Value -> Parser CallbackQueryAnswer
toEncodingList :: [CustomRequestResult] -> Encoding
$ctoEncodingList :: [CustomRequestResult] -> Encoding
toJSONList :: [CustomRequestResult] -> Value
$ctoJSONList :: [CustomRequestResult] -> Value
toEncoding :: CustomRequestResult -> Encoding
$ctoEncoding :: CustomRequestResult -> Encoding
toJSON :: CustomRequestResult -> Value
$ctoJSON :: CustomRequestResult -> Value
parseJSONList :: Value -> Parser [CustomRequestResult]
$cparseJSONList :: Value -> Parser [CustomRequestResult]
parseJSON :: Value -> Parser CustomRequestResult
$cparseJSON :: Value -> Parser CustomRequestResult
toEncodingList :: [GameHighScore] -> Encoding
$ctoEncodingList :: [GameHighScore] -> Encoding
toJSONList :: [GameHighScore] -> Value
$ctoJSONList :: [GameHighScore] -> Value
toEncoding :: GameHighScore -> Encoding
$ctoEncoding :: GameHighScore -> Encoding
toJSON :: GameHighScore -> Value
$ctoJSON :: GameHighScore -> Value
parseJSONList :: Value -> Parser [GameHighScore]
$cparseJSONList :: Value -> Parser [GameHighScore]
parseJSON :: Value -> Parser GameHighScore
$cparseJSON :: Value -> Parser GameHighScore
toEncodingList :: [GameHighScores] -> Encoding
$ctoEncodingList :: [GameHighScores] -> Encoding
toJSONList :: [GameHighScores] -> Value
$ctoJSONList :: [GameHighScores] -> Value
toEncoding :: GameHighScores -> Encoding
$ctoEncoding :: GameHighScores -> Encoding
toJSON :: GameHighScores -> Value
$ctoJSON :: GameHighScores -> Value
parseJSONList :: Value -> Parser [GameHighScores]
$cparseJSONList :: Value -> Parser [GameHighScores]
parseJSON :: Value -> Parser GameHighScores
$cparseJSON :: Value -> Parser GameHighScores
toEncodingList :: [ChatEventAction] -> Encoding
$ctoEncodingList :: [ChatEventAction] -> Encoding
toJSONList :: [ChatEventAction] -> Value
$ctoJSONList :: [ChatEventAction] -> Value
toEncoding :: ChatEventAction -> Encoding
$ctoEncoding :: ChatEventAction -> Encoding
toJSON :: ChatEventAction -> Value
$ctoJSON :: ChatEventAction -> Value
parseJSONList :: Value -> Parser [ChatEventAction]
$cparseJSONList :: Value -> Parser [ChatEventAction]
parseJSON :: Value -> Parser ChatEventAction
$cparseJSON :: Value -> Parser ChatEventAction
toEncodingList :: [ChatEvent] -> Encoding
$ctoEncodingList :: [ChatEvent] -> Encoding
toJSONList :: [ChatEvent] -> Value
$ctoJSONList :: [ChatEvent] -> Value
toEncoding :: ChatEvent -> Encoding
$ctoEncoding :: ChatEvent -> Encoding
toJSON :: ChatEvent -> Value
$ctoJSON :: ChatEvent -> Value
parseJSONList :: Value -> Parser [ChatEvent]
$cparseJSONList :: Value -> Parser [ChatEvent]
parseJSON :: Value -> Parser ChatEvent
$cparseJSON :: Value -> Parser ChatEvent
toEncodingList :: [ChatEvents] -> Encoding
$ctoEncodingList :: [ChatEvents] -> Encoding
toJSONList :: [ChatEvents] -> Value
$ctoJSONList :: [ChatEvents] -> Value
toEncoding :: ChatEvents -> Encoding
$ctoEncoding :: ChatEvents -> Encoding
toJSON :: ChatEvents -> Value
$ctoJSON :: ChatEvents -> Value
parseJSONList :: Value -> Parser [ChatEvents]
$cparseJSONList :: Value -> Parser [ChatEvents]
parseJSON :: Value -> Parser ChatEvents
$cparseJSON :: Value -> Parser ChatEvents
toEncodingList :: [ChatEventLogFilters] -> Encoding
$ctoEncodingList :: [ChatEventLogFilters] -> Encoding
toJSONList :: [ChatEventLogFilters] -> Value
$ctoJSONList :: [ChatEventLogFilters] -> Value
toEncoding :: ChatEventLogFilters -> Encoding
$ctoEncoding :: ChatEventLogFilters -> Encoding
toJSON :: ChatEventLogFilters -> Value
$ctoJSON :: ChatEventLogFilters -> Value
parseJSONList :: Value -> Parser [ChatEventLogFilters]
$cparseJSONList :: Value -> Parser [ChatEventLogFilters]
parseJSON :: Value -> Parser ChatEventLogFilters
$cparseJSON :: Value -> Parser ChatEventLogFilters
toEncodingList :: [LanguagePackStringValue] -> Encoding
$ctoEncodingList :: [LanguagePackStringValue] -> Encoding
toJSONList :: [LanguagePackStringValue] -> Value
$ctoJSONList :: [LanguagePackStringValue] -> Value
toEncoding :: LanguagePackStringValue -> Encoding
$ctoEncoding :: LanguagePackStringValue -> Encoding
toJSON :: LanguagePackStringValue -> Value
$ctoJSON :: LanguagePackStringValue -> Value
parseJSONList :: Value -> Parser [LanguagePackStringValue]
$cparseJSONList :: Value -> Parser [LanguagePackStringValue]
parseJSON :: Value -> Parser LanguagePackStringValue
$cparseJSON :: Value -> Parser LanguagePackStringValue
toEncodingList :: [LanguagePackString] -> Encoding
$ctoEncodingList :: [LanguagePackString] -> Encoding
toJSONList :: [LanguagePackString] -> Value
$ctoJSONList :: [LanguagePackString] -> Value
toEncoding :: LanguagePackString -> Encoding
$ctoEncoding :: LanguagePackString -> Encoding
toJSON :: LanguagePackString -> Value
$ctoJSON :: LanguagePackString -> Value
parseJSONList :: Value -> Parser [LanguagePackString]
$cparseJSONList :: Value -> Parser [LanguagePackString]
parseJSON :: Value -> Parser LanguagePackString
$cparseJSON :: Value -> Parser LanguagePackString
toEncodingList :: [LanguagePackStrings] -> Encoding
$ctoEncodingList :: [LanguagePackStrings] -> Encoding
toJSONList :: [LanguagePackStrings] -> Value
$ctoJSONList :: [LanguagePackStrings] -> Value
toEncoding :: LanguagePackStrings -> Encoding
$ctoEncoding :: LanguagePackStrings -> Encoding
toJSON :: LanguagePackStrings -> Value
$ctoJSON :: LanguagePackStrings -> Value
parseJSONList :: Value -> Parser [LanguagePackStrings]
$cparseJSONList :: Value -> Parser [LanguagePackStrings]
parseJSON :: Value -> Parser LanguagePackStrings
$cparseJSON :: Value -> Parser LanguagePackStrings
toEncodingList :: [LanguagePackInfo] -> Encoding
$ctoEncodingList :: [LanguagePackInfo] -> Encoding
toJSONList :: [LanguagePackInfo] -> Value
$ctoJSONList :: [LanguagePackInfo] -> Value
toEncoding :: LanguagePackInfo -> Encoding
$ctoEncoding :: LanguagePackInfo -> Encoding
toJSON :: LanguagePackInfo -> Value
$ctoJSON :: LanguagePackInfo -> Value
parseJSONList :: Value -> Parser [LanguagePackInfo]
$cparseJSONList :: Value -> Parser [LanguagePackInfo]
parseJSON :: Value -> Parser LanguagePackInfo
$cparseJSON :: Value -> Parser LanguagePackInfo
toEncodingList :: [LocalizationTargetInfo] -> Encoding
$ctoEncodingList :: [LocalizationTargetInfo] -> Encoding
toJSONList :: [LocalizationTargetInfo] -> Value
$ctoJSONList :: [LocalizationTargetInfo] -> Value
toEncoding :: LocalizationTargetInfo -> Encoding
$ctoEncoding :: LocalizationTargetInfo -> Encoding
toJSON :: LocalizationTargetInfo -> Value
$ctoJSON :: LocalizationTargetInfo -> Value
parseJSONList :: Value -> Parser [LocalizationTargetInfo]
$cparseJSONList :: Value -> Parser [LocalizationTargetInfo]
parseJSON :: Value -> Parser LocalizationTargetInfo
$cparseJSON :: Value -> Parser LocalizationTargetInfo
toEncodingList :: [DeviceToken] -> Encoding
$ctoEncodingList :: [DeviceToken] -> Encoding
toJSONList :: [DeviceToken] -> Value
$ctoJSONList :: [DeviceToken] -> Value
toEncoding :: DeviceToken -> Encoding
$ctoEncoding :: DeviceToken -> Encoding
toJSON :: DeviceToken -> Value
$ctoJSON :: DeviceToken -> Value
parseJSONList :: Value -> Parser [DeviceToken]
$cparseJSONList :: Value -> Parser [DeviceToken]
parseJSON :: Value -> Parser DeviceToken
$cparseJSON :: Value -> Parser DeviceToken
toEncodingList :: [PushReceiverId] -> Encoding
$ctoEncodingList :: [PushReceiverId] -> Encoding
toJSONList :: [PushReceiverId] -> Value
$ctoJSONList :: [PushReceiverId] -> Value
toEncoding :: PushReceiverId -> Encoding
$ctoEncoding :: PushReceiverId -> Encoding
toJSON :: PushReceiverId -> Value
$ctoJSON :: PushReceiverId -> Value
parseJSONList :: Value -> Parser [PushReceiverId]
$cparseJSONList :: Value -> Parser [PushReceiverId]
parseJSON :: Value -> Parser PushReceiverId
$cparseJSON :: Value -> Parser PushReceiverId
toEncodingList :: [BackgroundFill] -> Encoding
$ctoEncodingList :: [BackgroundFill] -> Encoding
toJSONList :: [BackgroundFill] -> Value
$ctoJSONList :: [BackgroundFill] -> Value
toEncoding :: BackgroundFill -> Encoding
$ctoEncoding :: BackgroundFill -> Encoding
toJSON :: BackgroundFill -> Value
$ctoJSON :: BackgroundFill -> Value
parseJSONList :: Value -> Parser [BackgroundFill]
$cparseJSONList :: Value -> Parser [BackgroundFill]
parseJSON :: Value -> Parser BackgroundFill
$cparseJSON :: Value -> Parser BackgroundFill
toEncodingList :: [BackgroundType] -> Encoding
$ctoEncodingList :: [BackgroundType] -> Encoding
toJSONList :: [BackgroundType] -> Value
$ctoJSONList :: [BackgroundType] -> Value
toEncoding :: BackgroundType -> Encoding
$ctoEncoding :: BackgroundType -> Encoding
toJSON :: BackgroundType -> Value
$ctoJSON :: BackgroundType -> Value
parseJSONList :: Value -> Parser [BackgroundType]
$cparseJSONList :: Value -> Parser [BackgroundType]
parseJSON :: Value -> Parser BackgroundType
$cparseJSON :: Value -> Parser BackgroundType
toEncodingList :: [Background] -> Encoding
$ctoEncodingList :: [Background] -> Encoding
toJSONList :: [Background] -> Value
$ctoJSONList :: [Background] -> Value
toEncoding :: Background -> Encoding
$ctoEncoding :: Background -> Encoding
toJSON :: Background -> Value
$ctoJSON :: Background -> Value
parseJSONList :: Value -> Parser [Background]
$cparseJSONList :: Value -> Parser [Background]
parseJSON :: Value -> Parser Background
$cparseJSON :: Value -> Parser Background
toEncodingList :: [Backgrounds] -> Encoding
$ctoEncodingList :: [Backgrounds] -> Encoding
toJSONList :: [Backgrounds] -> Value
$ctoJSONList :: [Backgrounds] -> Value
toEncoding :: Backgrounds -> Encoding
$ctoEncoding :: Backgrounds -> Encoding
toJSON :: Backgrounds -> Value
$ctoJSON :: Backgrounds -> Value
parseJSONList :: Value -> Parser [Backgrounds]
$cparseJSONList :: Value -> Parser [Backgrounds]
parseJSON :: Value -> Parser Backgrounds
$cparseJSON :: Value -> Parser Backgrounds
toEncodingList :: [InputBackground] -> Encoding
$ctoEncodingList :: [InputBackground] -> Encoding
toJSONList :: [InputBackground] -> Value
$ctoJSONList :: [InputBackground] -> Value
toEncoding :: InputBackground -> Encoding
$ctoEncoding :: InputBackground -> Encoding
toJSON :: InputBackground -> Value
$ctoJSON :: InputBackground -> Value
parseJSONList :: Value -> Parser [InputBackground]
$cparseJSONList :: Value -> Parser [InputBackground]
parseJSON :: Value -> Parser InputBackground
$cparseJSON :: Value -> Parser InputBackground
toEncodingList :: [Hashtags] -> Encoding
$ctoEncodingList :: [Hashtags] -> Encoding
toJSONList :: [Hashtags] -> Value
$ctoJSONList :: [Hashtags] -> Value
toEncoding :: Hashtags -> Encoding
$ctoEncoding :: Hashtags -> Encoding
toJSON :: Hashtags -> Value
$ctoJSON :: Hashtags -> Value
parseJSONList :: Value -> Parser [Hashtags]
$cparseJSONList :: Value -> Parser [Hashtags]
parseJSON :: Value -> Parser Hashtags
$cparseJSON :: Value -> Parser Hashtags
toEncodingList :: [CanTransferOwnershipResult] -> Encoding
$ctoEncodingList :: [CanTransferOwnershipResult] -> Encoding
toJSONList :: [CanTransferOwnershipResult] -> Value
$ctoJSONList :: [CanTransferOwnershipResult] -> Value
toEncoding :: CanTransferOwnershipResult -> Encoding
$ctoEncoding :: CanTransferOwnershipResult -> Encoding
toJSON :: CanTransferOwnershipResult -> Value
$ctoJSON :: CanTransferOwnershipResult -> Value
parseJSONList :: Value -> Parser [CanTransferOwnershipResult]
$cparseJSONList :: Value -> Parser [CanTransferOwnershipResult]
parseJSON :: Value -> Parser CanTransferOwnershipResult
$cparseJSON :: Value -> Parser CanTransferOwnershipResult
toEncodingList :: [CheckChatUsernameResult] -> Encoding
$ctoEncodingList :: [CheckChatUsernameResult] -> Encoding
toJSONList :: [CheckChatUsernameResult] -> Value
$ctoJSONList :: [CheckChatUsernameResult] -> Value
toEncoding :: CheckChatUsernameResult -> Encoding
$ctoEncoding :: CheckChatUsernameResult -> Encoding
toJSON :: CheckChatUsernameResult -> Value
$ctoJSON :: CheckChatUsernameResult -> Value
parseJSONList :: Value -> Parser [CheckChatUsernameResult]
$cparseJSONList :: Value -> Parser [CheckChatUsernameResult]
parseJSON :: Value -> Parser CheckChatUsernameResult
$cparseJSON :: Value -> Parser CheckChatUsernameResult
toEncodingList :: [PushMessageContent] -> Encoding
$ctoEncodingList :: [PushMessageContent] -> Encoding
toJSONList :: [PushMessageContent] -> Value
$ctoJSONList :: [PushMessageContent] -> Value
toEncoding :: PushMessageContent -> Encoding
$ctoEncoding :: PushMessageContent -> Encoding
toJSON :: PushMessageContent -> Value
$ctoJSON :: PushMessageContent -> Value
parseJSONList :: Value -> Parser [PushMessageContent]
$cparseJSONList :: Value -> Parser [PushMessageContent]
parseJSON :: Value -> Parser PushMessageContent
$cparseJSON :: Value -> Parser PushMessageContent
toEncodingList :: [NotificationType] -> Encoding
$ctoEncodingList :: [NotificationType] -> Encoding
toJSONList :: [NotificationType] -> Value
$ctoJSONList :: [NotificationType] -> Value
toEncoding :: NotificationType -> Encoding
$ctoEncoding :: NotificationType -> Encoding
toJSON :: NotificationType -> Value
$ctoJSON :: NotificationType -> Value
parseJSONList :: Value -> Parser [NotificationType]
$cparseJSONList :: Value -> Parser [NotificationType]
parseJSON :: Value -> Parser NotificationType
$cparseJSON :: Value -> Parser NotificationType
toEncodingList :: [NotificationGroupType] -> Encoding
$ctoEncodingList :: [NotificationGroupType] -> Encoding
toJSONList :: [NotificationGroupType] -> Value
$ctoJSONList :: [NotificationGroupType] -> Value
toEncoding :: NotificationGroupType -> Encoding
$ctoEncoding :: NotificationGroupType -> Encoding
toJSON :: NotificationGroupType -> Value
$ctoJSON :: NotificationGroupType -> Value
parseJSONList :: Value -> Parser [NotificationGroupType]
$cparseJSONList :: Value -> Parser [NotificationGroupType]
parseJSON :: Value -> Parser NotificationGroupType
$cparseJSON :: Value -> Parser NotificationGroupType
toEncodingList :: [Notification] -> Encoding
$ctoEncodingList :: [Notification] -> Encoding
toJSONList :: [Notification] -> Value
$ctoJSONList :: [Notification] -> Value
toEncoding :: Notification -> Encoding
$ctoEncoding :: Notification -> Encoding
toJSON :: Notification -> Value
$ctoJSON :: Notification -> Value
parseJSONList :: Value -> Parser [Notification]
$cparseJSONList :: Value -> Parser [Notification]
parseJSON :: Value -> Parser Notification
$cparseJSON :: Value -> Parser Notification
toEncodingList :: [NotificationGroup] -> Encoding
$ctoEncodingList :: [NotificationGroup] -> Encoding
toJSONList :: [NotificationGroup] -> Value
$ctoJSONList :: [NotificationGroup] -> Value
toEncoding :: NotificationGroup -> Encoding
$ctoEncoding :: NotificationGroup -> Encoding
toJSON :: NotificationGroup -> Value
$ctoJSON :: NotificationGroup -> Value
parseJSONList :: Value -> Parser [NotificationGroup]
$cparseJSONList :: Value -> Parser [NotificationGroup]
parseJSON :: Value -> Parser NotificationGroup
$cparseJSON :: Value -> Parser NotificationGroup
toEncodingList :: [OptionValue] -> Encoding
$ctoEncodingList :: [OptionValue] -> Encoding
toJSONList :: [OptionValue] -> Value
$ctoJSONList :: [OptionValue] -> Value
toEncoding :: OptionValue -> Encoding
$ctoEncoding :: OptionValue -> Encoding
toJSON :: OptionValue -> Value
$ctoJSON :: OptionValue -> Value
parseJSONList :: Value -> Parser [OptionValue]
$cparseJSONList :: Value -> Parser [OptionValue]
parseJSON :: Value -> Parser OptionValue
$cparseJSON :: Value -> Parser OptionValue
toEncodingList :: [JsonObjectMember] -> Encoding
$ctoEncodingList :: [JsonObjectMember] -> Encoding
toJSONList :: [JsonObjectMember] -> Value
$ctoJSONList :: [JsonObjectMember] -> Value
toEncoding :: JsonObjectMember -> Encoding
$ctoEncoding :: JsonObjectMember -> Encoding
toJSON :: JsonObjectMember -> Value
$ctoJSON :: JsonObjectMember -> Value
parseJSONList :: Value -> Parser [JsonObjectMember]
$cparseJSONList :: Value -> Parser [JsonObjectMember]
parseJSON :: Value -> Parser JsonObjectMember
$cparseJSON :: Value -> Parser JsonObjectMember
toEncodingList :: [JsonValue] -> Encoding
$ctoEncodingList :: [JsonValue] -> Encoding
toJSONList :: [JsonValue] -> Value
$ctoJSONList :: [JsonValue] -> Value
toEncoding :: JsonValue -> Encoding
$ctoEncoding :: JsonValue -> Encoding
toJSON :: JsonValue -> Value
$ctoJSON :: JsonValue -> Value
parseJSONList :: Value -> Parser [JsonValue]
$cparseJSONList :: Value -> Parser [JsonValue]
parseJSON :: Value -> Parser JsonValue
$cparseJSON :: Value -> Parser JsonValue
toEncodingList :: [UserPrivacySettingRule] -> Encoding
$ctoEncodingList :: [UserPrivacySettingRule] -> Encoding
toJSONList :: [UserPrivacySettingRule] -> Value
$ctoJSONList :: [UserPrivacySettingRule] -> Value
toEncoding :: UserPrivacySettingRule -> Encoding
$ctoEncoding :: UserPrivacySettingRule -> Encoding
toJSON :: UserPrivacySettingRule -> Value
$ctoJSON :: UserPrivacySettingRule -> Value
parseJSONList :: Value -> Parser [UserPrivacySettingRule]
$cparseJSONList :: Value -> Parser [UserPrivacySettingRule]
parseJSON :: Value -> Parser UserPrivacySettingRule
$cparseJSON :: Value -> Parser UserPrivacySettingRule
toEncodingList :: [UserPrivacySettingRules] -> Encoding
$ctoEncodingList :: [UserPrivacySettingRules] -> Encoding
toJSONList :: [UserPrivacySettingRules] -> Value
$ctoJSONList :: [UserPrivacySettingRules] -> Value
toEncoding :: UserPrivacySettingRules -> Encoding
$ctoEncoding :: UserPrivacySettingRules -> Encoding
toJSON :: UserPrivacySettingRules -> Value
$ctoJSON :: UserPrivacySettingRules -> Value
parseJSONList :: Value -> Parser [UserPrivacySettingRules]
$cparseJSONList :: Value -> Parser [UserPrivacySettingRules]
parseJSON :: Value -> Parser UserPrivacySettingRules
$cparseJSON :: Value -> Parser UserPrivacySettingRules
toEncodingList :: [UserPrivacySetting] -> Encoding
$ctoEncodingList :: [UserPrivacySetting] -> Encoding
toJSONList :: [UserPrivacySetting] -> Value
$ctoJSONList :: [UserPrivacySetting] -> Value
toEncoding :: UserPrivacySetting -> Encoding
$ctoEncoding :: UserPrivacySetting -> Encoding
toJSON :: UserPrivacySetting -> Value
$ctoJSON :: UserPrivacySetting -> Value
parseJSONList :: Value -> Parser [UserPrivacySetting]
$cparseJSONList :: Value -> Parser [UserPrivacySetting]
parseJSON :: Value -> Parser UserPrivacySetting
$cparseJSON :: Value -> Parser UserPrivacySetting
toEncodingList :: [AccountTtl] -> Encoding
$ctoEncodingList :: [AccountTtl] -> Encoding
toJSONList :: [AccountTtl] -> Value
$ctoJSONList :: [AccountTtl] -> Value
toEncoding :: AccountTtl -> Encoding
$ctoEncoding :: AccountTtl -> Encoding
toJSON :: AccountTtl -> Value
$ctoJSON :: AccountTtl -> Value
parseJSONList :: Value -> Parser [AccountTtl]
$cparseJSONList :: Value -> Parser [AccountTtl]
parseJSON :: Value -> Parser AccountTtl
$cparseJSON :: Value -> Parser AccountTtl
toEncodingList :: [Session] -> Encoding
$ctoEncodingList :: [Session] -> Encoding
toJSONList :: [Session] -> Value
$ctoJSONList :: [Session] -> Value
toEncoding :: Session -> Encoding
$ctoEncoding :: Session -> Encoding
toJSON :: Session -> Value
$ctoJSON :: Session -> Value
parseJSONList :: Value -> Parser [Session]
$cparseJSONList :: Value -> Parser [Session]
parseJSON :: Value -> Parser Session
$cparseJSON :: Value -> Parser Session
toEncodingList :: [Sessions] -> Encoding
$ctoEncodingList :: [Sessions] -> Encoding
toJSONList :: [Sessions] -> Value
$ctoJSONList :: [Sessions] -> Value
toEncoding :: Sessions -> Encoding
$ctoEncoding :: Sessions -> Encoding
toJSON :: Sessions -> Value
$ctoJSON :: Sessions -> Value
parseJSONList :: Value -> Parser [Sessions]
$cparseJSONList :: Value -> Parser [Sessions]
parseJSON :: Value -> Parser Sessions
$cparseJSON :: Value -> Parser Sessions
toEncodingList :: [ConnectedWebsite] -> Encoding
$ctoEncodingList :: [ConnectedWebsite] -> Encoding
toJSONList :: [ConnectedWebsite] -> Value
$ctoJSONList :: [ConnectedWebsite] -> Value
toEncoding :: ConnectedWebsite -> Encoding
$ctoEncoding :: ConnectedWebsite -> Encoding
toJSON :: ConnectedWebsite -> Value
$ctoJSON :: ConnectedWebsite -> Value
parseJSONList :: Value -> Parser [ConnectedWebsite]
$cparseJSONList :: Value -> Parser [ConnectedWebsite]
parseJSON :: Value -> Parser ConnectedWebsite
$cparseJSON :: Value -> Parser ConnectedWebsite
toEncodingList :: [ConnectedWebsites] -> Encoding
$ctoEncodingList :: [ConnectedWebsites] -> Encoding
toJSONList :: [ConnectedWebsites] -> Value
$ctoJSONList :: [ConnectedWebsites] -> Value
toEncoding :: ConnectedWebsites -> Encoding
$ctoEncoding :: ConnectedWebsites -> Encoding
toJSON :: ConnectedWebsites -> Value
$ctoJSON :: ConnectedWebsites -> Value
parseJSONList :: Value -> Parser [ConnectedWebsites]
$cparseJSONList :: Value -> Parser [ConnectedWebsites]
parseJSON :: Value -> Parser ConnectedWebsites
$cparseJSON :: Value -> Parser ConnectedWebsites
toEncodingList :: [ChatReportReason] -> Encoding
$ctoEncodingList :: [ChatReportReason] -> Encoding
toJSONList :: [ChatReportReason] -> Value
$ctoJSONList :: [ChatReportReason] -> Value
toEncoding :: ChatReportReason -> Encoding
$ctoEncoding :: ChatReportReason -> Encoding
toJSON :: ChatReportReason -> Value
$ctoJSON :: ChatReportReason -> Value
parseJSONList :: Value -> Parser [ChatReportReason]
$cparseJSONList :: Value -> Parser [ChatReportReason]
parseJSON :: Value -> Parser ChatReportReason
$cparseJSON :: Value -> Parser ChatReportReason
toEncodingList :: [PublicMessageLink] -> Encoding
$ctoEncodingList :: [PublicMessageLink] -> Encoding
toJSONList :: [PublicMessageLink] -> Value
$ctoJSONList :: [PublicMessageLink] -> Value
toEncoding :: PublicMessageLink -> Encoding
$ctoEncoding :: PublicMessageLink -> Encoding
toJSON :: PublicMessageLink -> Value
$ctoJSON :: PublicMessageLink -> Value
parseJSONList :: Value -> Parser [PublicMessageLink]
$cparseJSONList :: Value -> Parser [PublicMessageLink]
parseJSON :: Value -> Parser PublicMessageLink
$cparseJSON :: Value -> Parser PublicMessageLink
toEncodingList :: [MessageLinkInfo] -> Encoding
$ctoEncodingList :: [MessageLinkInfo] -> Encoding
toJSONList :: [MessageLinkInfo] -> Value
$ctoJSONList :: [MessageLinkInfo] -> Value
toEncoding :: MessageLinkInfo -> Encoding
$ctoEncoding :: MessageLinkInfo -> Encoding
toJSON :: MessageLinkInfo -> Value
$ctoJSON :: MessageLinkInfo -> Value
parseJSONList :: Value -> Parser [MessageLinkInfo]
$cparseJSONList :: Value -> Parser [MessageLinkInfo]
parseJSON :: Value -> Parser MessageLinkInfo
$cparseJSON :: Value -> Parser MessageLinkInfo
toEncodingList :: [FilePart] -> Encoding
$ctoEncodingList :: [FilePart] -> Encoding
toJSONList :: [FilePart] -> Value
$ctoJSONList :: [FilePart] -> Value
toEncoding :: FilePart -> Encoding
$ctoEncoding :: FilePart -> Encoding
toJSON :: FilePart -> Value
$ctoJSON :: FilePart -> Value
parseJSONList :: Value -> Parser [FilePart]
$cparseJSONList :: Value -> Parser [FilePart]
parseJSON :: Value -> Parser FilePart
$cparseJSON :: Value -> Parser FilePart
toEncodingList :: [FileType] -> Encoding
$ctoEncodingList :: [FileType] -> Encoding
toJSONList :: [FileType] -> Value
$ctoJSONList :: [FileType] -> Value
toEncoding :: FileType -> Encoding
$ctoEncoding :: FileType -> Encoding
toJSON :: FileType -> Value
$ctoJSON :: FileType -> Value
parseJSONList :: Value -> Parser [FileType]
$cparseJSONList :: Value -> Parser [FileType]
parseJSON :: Value -> Parser FileType
$cparseJSON :: Value -> Parser FileType
toEncodingList :: [StorageStatisticsByFileType] -> Encoding
$ctoEncodingList :: [StorageStatisticsByFileType] -> Encoding
toJSONList :: [StorageStatisticsByFileType] -> Value
$ctoJSONList :: [StorageStatisticsByFileType] -> Value
toEncoding :: StorageStatisticsByFileType -> Encoding
$ctoEncoding :: StorageStatisticsByFileType -> Encoding
toJSON :: StorageStatisticsByFileType -> Value
$ctoJSON :: StorageStatisticsByFileType -> Value
parseJSONList :: Value -> Parser [StorageStatisticsByFileType]
$cparseJSONList :: Value -> Parser [StorageStatisticsByFileType]
parseJSON :: Value -> Parser StorageStatisticsByFileType
$cparseJSON :: Value -> Parser StorageStatisticsByFileType
toEncodingList :: [StorageStatisticsByChat] -> Encoding
$ctoEncodingList :: [StorageStatisticsByChat] -> Encoding
toJSONList :: [StorageStatisticsByChat] -> Value
$ctoJSONList :: [StorageStatisticsByChat] -> Value
toEncoding :: StorageStatisticsByChat -> Encoding
$ctoEncoding :: StorageStatisticsByChat -> Encoding
toJSON :: StorageStatisticsByChat -> Value
$ctoJSON :: StorageStatisticsByChat -> Value
parseJSONList :: Value -> Parser [StorageStatisticsByChat]
$cparseJSONList :: Value -> Parser [StorageStatisticsByChat]
parseJSON :: Value -> Parser StorageStatisticsByChat
$cparseJSON :: Value -> Parser StorageStatisticsByChat
toEncodingList :: [StorageStatistics] -> Encoding
$ctoEncodingList :: [StorageStatistics] -> Encoding
toJSONList :: [StorageStatistics] -> Value
$ctoJSONList :: [StorageStatistics] -> Value
toEncoding :: StorageStatistics -> Encoding
$ctoEncoding :: StorageStatistics -> Encoding
toJSON :: StorageStatistics -> Value
$ctoJSON :: StorageStatistics -> Value
parseJSONList :: Value -> Parser [StorageStatistics]
$cparseJSONList :: Value -> Parser [StorageStatistics]
parseJSON :: Value -> Parser StorageStatistics
$cparseJSON :: Value -> Parser StorageStatistics
toEncodingList :: [StorageStatisticsFast] -> Encoding
$ctoEncodingList :: [StorageStatisticsFast] -> Encoding
toJSONList :: [StorageStatisticsFast] -> Value
$ctoJSONList :: [StorageStatisticsFast] -> Value
toEncoding :: StorageStatisticsFast -> Encoding
$ctoEncoding :: StorageStatisticsFast -> Encoding
toJSON :: StorageStatisticsFast -> Value
$ctoJSON :: StorageStatisticsFast -> Value
parseJSONList :: Value -> Parser [StorageStatisticsFast]
$cparseJSONList :: Value -> Parser [StorageStatisticsFast]
parseJSON :: Value -> Parser StorageStatisticsFast
$cparseJSON :: Value -> Parser StorageStatisticsFast
toEncodingList :: [DatabaseStatistics] -> Encoding
$ctoEncodingList :: [DatabaseStatistics] -> Encoding
toJSONList :: [DatabaseStatistics] -> Value
$ctoJSONList :: [DatabaseStatistics] -> Value
toEncoding :: DatabaseStatistics -> Encoding
$ctoEncoding :: DatabaseStatistics -> Encoding
toJSON :: DatabaseStatistics -> Value
$ctoJSON :: DatabaseStatistics -> Value
parseJSONList :: Value -> Parser [DatabaseStatistics]
$cparseJSONList :: Value -> Parser [DatabaseStatistics]
parseJSON :: Value -> Parser DatabaseStatistics
$cparseJSON :: Value -> Parser DatabaseStatistics
toEncodingList :: [NetworkType] -> Encoding
$ctoEncodingList :: [NetworkType] -> Encoding
toJSONList :: [NetworkType] -> Value
$ctoJSONList :: [NetworkType] -> Value
toEncoding :: NetworkType -> Encoding
$ctoEncoding :: NetworkType -> Encoding
toJSON :: NetworkType -> Value
$ctoJSON :: NetworkType -> Value
parseJSONList :: Value -> Parser [NetworkType]
$cparseJSONList :: Value -> Parser [NetworkType]
parseJSON :: Value -> Parser NetworkType
$cparseJSON :: Value -> Parser NetworkType
toEncodingList :: [NetworkStatisticsEntry] -> Encoding
$ctoEncodingList :: [NetworkStatisticsEntry] -> Encoding
toJSONList :: [NetworkStatisticsEntry] -> Value
$ctoJSONList :: [NetworkStatisticsEntry] -> Value
toEncoding :: NetworkStatisticsEntry -> Encoding
$ctoEncoding :: NetworkStatisticsEntry -> Encoding
toJSON :: NetworkStatisticsEntry -> Value
$ctoJSON :: NetworkStatisticsEntry -> Value
parseJSONList :: Value -> Parser [NetworkStatisticsEntry]
$cparseJSONList :: Value -> Parser [NetworkStatisticsEntry]
parseJSON :: Value -> Parser NetworkStatisticsEntry
$cparseJSON :: Value -> Parser NetworkStatisticsEntry
toEncodingList :: [NetworkStatistics] -> Encoding
$ctoEncodingList :: [NetworkStatistics] -> Encoding
toJSONList :: [NetworkStatistics] -> Value
$ctoJSONList :: [NetworkStatistics] -> Value
toEncoding :: NetworkStatistics -> Encoding
$ctoEncoding :: NetworkStatistics -> Encoding
toJSON :: NetworkStatistics -> Value
$ctoJSON :: NetworkStatistics -> Value
parseJSONList :: Value -> Parser [NetworkStatistics]
$cparseJSONList :: Value -> Parser [NetworkStatistics]
parseJSON :: Value -> Parser NetworkStatistics
$cparseJSON :: Value -> Parser NetworkStatistics
toEncodingList :: [AutoDownloadSettings] -> Encoding
$ctoEncodingList :: [AutoDownloadSettings] -> Encoding
toJSONList :: [AutoDownloadSettings] -> Value
$ctoJSONList :: [AutoDownloadSettings] -> Value
toEncoding :: AutoDownloadSettings -> Encoding
$ctoEncoding :: AutoDownloadSettings -> Encoding
toJSON :: AutoDownloadSettings -> Value
$ctoJSON :: AutoDownloadSettings -> Value
parseJSONList :: Value -> Parser [AutoDownloadSettings]
$cparseJSONList :: Value -> Parser [AutoDownloadSettings]
parseJSON :: Value -> Parser AutoDownloadSettings
$cparseJSON :: Value -> Parser AutoDownloadSettings
toEncodingList :: [AutoDownloadSettingsPresets] -> Encoding
$ctoEncodingList :: [AutoDownloadSettingsPresets] -> Encoding
toJSONList :: [AutoDownloadSettingsPresets] -> Value
$ctoJSONList :: [AutoDownloadSettingsPresets] -> Value
toEncoding :: AutoDownloadSettingsPresets -> Encoding
$ctoEncoding :: AutoDownloadSettingsPresets -> Encoding
toJSON :: AutoDownloadSettingsPresets -> Value
$ctoJSON :: AutoDownloadSettingsPresets -> Value
parseJSONList :: Value -> Parser [AutoDownloadSettingsPresets]
$cparseJSONList :: Value -> Parser [AutoDownloadSettingsPresets]
parseJSON :: Value -> Parser AutoDownloadSettingsPresets
$cparseJSON :: Value -> Parser AutoDownloadSettingsPresets
toEncodingList :: [ConnectionState] -> Encoding
$ctoEncodingList :: [ConnectionState] -> Encoding
toJSONList :: [ConnectionState] -> Value
$ctoJSONList :: [ConnectionState] -> Value
toEncoding :: ConnectionState -> Encoding
$ctoEncoding :: ConnectionState -> Encoding
toJSON :: ConnectionState -> Value
$ctoJSON :: ConnectionState -> Value
parseJSONList :: Value -> Parser [ConnectionState]
$cparseJSONList :: Value -> Parser [ConnectionState]
parseJSON :: Value -> Parser ConnectionState
$cparseJSON :: Value -> Parser ConnectionState
toEncodingList :: [TopChatCategory] -> Encoding
$ctoEncodingList :: [TopChatCategory] -> Encoding
toJSONList :: [TopChatCategory] -> Value
$ctoJSONList :: [TopChatCategory] -> Value
toEncoding :: TopChatCategory -> Encoding
$ctoEncoding :: TopChatCategory -> Encoding
toJSON :: TopChatCategory -> Value
$ctoJSON :: TopChatCategory -> Value
parseJSONList :: Value -> Parser [TopChatCategory]
$cparseJSONList :: Value -> Parser [TopChatCategory]
parseJSON :: Value -> Parser TopChatCategory
$cparseJSON :: Value -> Parser TopChatCategory
toEncodingList :: [TMeUrlType] -> Encoding
$ctoEncodingList :: [TMeUrlType] -> Encoding
toJSONList :: [TMeUrlType] -> Value
$ctoJSONList :: [TMeUrlType] -> Value
toEncoding :: TMeUrlType -> Encoding
$ctoEncoding :: TMeUrlType -> Encoding
toJSON :: TMeUrlType -> Value
$ctoJSON :: TMeUrlType -> Value
parseJSONList :: Value -> Parser [TMeUrlType]
$cparseJSONList :: Value -> Parser [TMeUrlType]
parseJSON :: Value -> Parser TMeUrlType
$cparseJSON :: Value -> Parser TMeUrlType
toEncodingList :: [TMeUrl] -> Encoding
$ctoEncodingList :: [TMeUrl] -> Encoding
toJSONList :: [TMeUrl] -> Value
$ctoJSONList :: [TMeUrl] -> Value
toEncoding :: TMeUrl -> Encoding
$ctoEncoding :: TMeUrl -> Encoding
toJSON :: TMeUrl -> Value
$ctoJSON :: TMeUrl -> Value
parseJSONList :: Value -> Parser [TMeUrl]
$cparseJSONList :: Value -> Parser [TMeUrl]
parseJSON :: Value -> Parser TMeUrl
$cparseJSON :: Value -> Parser TMeUrl
toEncodingList :: [TMeUrls] -> Encoding
$ctoEncodingList :: [TMeUrls] -> Encoding
toJSONList :: [TMeUrls] -> Value
$ctoJSONList :: [TMeUrls] -> Value
toEncoding :: TMeUrls -> Encoding
$ctoEncoding :: TMeUrls -> Encoding
toJSON :: TMeUrls -> Value
$ctoJSON :: TMeUrls -> Value
parseJSONList :: Value -> Parser [TMeUrls]
$cparseJSONList :: Value -> Parser [TMeUrls]
parseJSON :: Value -> Parser TMeUrls
$cparseJSON :: Value -> Parser TMeUrls
toEncodingList :: [Count] -> Encoding
$ctoEncodingList :: [Count] -> Encoding
toJSONList :: [Count] -> Value
$ctoJSONList :: [Count] -> Value
toEncoding :: Count -> Encoding
$ctoEncoding :: Count -> Encoding
toJSON :: Count -> Value
$ctoJSON :: Count -> Value
parseJSONList :: Value -> Parser [Count]
$cparseJSONList :: Value -> Parser [Count]
parseJSON :: Value -> Parser Count
$cparseJSON :: Value -> Parser Count
toEncodingList :: [Text] -> Encoding
$ctoEncodingList :: [Text] -> Encoding
toJSONList :: [Text] -> Value
$ctoJSONList :: [Text] -> Value
toEncoding :: Text -> Encoding
$ctoEncoding :: Text -> Encoding
toJSON :: Text -> Value
$ctoJSON :: Text -> Value
parseJSONList :: Value -> Parser [Text]
$cparseJSONList :: Value -> Parser [Text]
parseJSON :: Value -> Parser Text
$cparseJSON :: Value -> Parser Text
toEncodingList :: [Seconds] -> Encoding
$ctoEncodingList :: [Seconds] -> Encoding
toJSONList :: [Seconds] -> Value
$ctoJSONList :: [Seconds] -> Value
toEncoding :: Seconds -> Encoding
$ctoEncoding :: Seconds -> Encoding
toJSON :: Seconds -> Value
$ctoJSON :: Seconds -> Value
parseJSONList :: Value -> Parser [Seconds]
$cparseJSONList :: Value -> Parser [Seconds]
parseJSON :: Value -> Parser Seconds
$cparseJSON :: Value -> Parser Seconds
toEncodingList :: [DeepLinkInfo] -> Encoding
$ctoEncodingList :: [DeepLinkInfo] -> Encoding
toJSONList :: [DeepLinkInfo] -> Value
$ctoJSONList :: [DeepLinkInfo] -> Value
toEncoding :: DeepLinkInfo -> Encoding
$ctoEncoding :: DeepLinkInfo -> Encoding
toJSON :: DeepLinkInfo -> Value
$ctoJSON :: DeepLinkInfo -> Value
parseJSONList :: Value -> Parser [DeepLinkInfo]
$cparseJSONList :: Value -> Parser [DeepLinkInfo]
parseJSON :: Value -> Parser DeepLinkInfo
$cparseJSON :: Value -> Parser DeepLinkInfo
toEncodingList :: [TextParseMode] -> Encoding
$ctoEncodingList :: [TextParseMode] -> Encoding
toJSONList :: [TextParseMode] -> Value
$ctoJSONList :: [TextParseMode] -> Value
toEncoding :: TextParseMode -> Encoding
$ctoEncoding :: TextParseMode -> Encoding
toJSON :: TextParseMode -> Value
$ctoJSON :: TextParseMode -> Value
parseJSONList :: Value -> Parser [TextParseMode]
$cparseJSONList :: Value -> Parser [TextParseMode]
parseJSON :: Value -> Parser TextParseMode
$cparseJSON :: Value -> Parser TextParseMode
toEncodingList :: [ProxyType] -> Encoding
$ctoEncodingList :: [ProxyType] -> Encoding
toJSONList :: [ProxyType] -> Value
$ctoJSONList :: [ProxyType] -> Value
toEncoding :: ProxyType -> Encoding
$ctoEncoding :: ProxyType -> Encoding
toJSON :: ProxyType -> Value
$ctoJSON :: ProxyType -> Value
parseJSONList :: Value -> Parser [ProxyType]
$cparseJSONList :: Value -> Parser [ProxyType]
parseJSON :: Value -> Parser ProxyType
$cparseJSON :: Value -> Parser ProxyType
toEncodingList :: [Proxy] -> Encoding
$ctoEncodingList :: [Proxy] -> Encoding
toJSONList :: [Proxy] -> Value
$ctoJSONList :: [Proxy] -> Value
toEncoding :: Proxy -> Encoding
$ctoEncoding :: Proxy -> Encoding
toJSON :: Proxy -> Value
$ctoJSON :: Proxy -> Value
parseJSONList :: Value -> Parser [Proxy]
$cparseJSONList :: Value -> Parser [Proxy]
parseJSON :: Value -> Parser Proxy
$cparseJSON :: Value -> Parser Proxy
toEncodingList :: [Proxies] -> Encoding
$ctoEncodingList :: [Proxies] -> Encoding
toJSONList :: [Proxies] -> Value
$ctoJSONList :: [Proxies] -> Value
toEncoding :: Proxies -> Encoding
$ctoEncoding :: Proxies -> Encoding
toJSON :: Proxies -> Value
$ctoJSON :: Proxies -> Value
parseJSONList :: Value -> Parser [Proxies]
$cparseJSONList :: Value -> Parser [Proxies]
parseJSON :: Value -> Parser Proxies
$cparseJSON :: Value -> Parser Proxies
toEncodingList :: [InputSticker] -> Encoding
$ctoEncodingList :: [InputSticker] -> Encoding
toJSONList :: [InputSticker] -> Value
$ctoJSONList :: [InputSticker] -> Value
toEncoding :: InputSticker -> Encoding
$ctoEncoding :: InputSticker -> Encoding
toJSON :: InputSticker -> Value
$ctoJSON :: InputSticker -> Value
parseJSONList :: Value -> Parser [InputSticker]
$cparseJSONList :: Value -> Parser [InputSticker]
parseJSON :: Value -> Parser InputSticker
$cparseJSON :: Value -> Parser InputSticker
toEncodingList :: [DateRange] -> Encoding
$ctoEncodingList :: [DateRange] -> Encoding
toJSONList :: [DateRange] -> Value
$ctoJSONList :: [DateRange] -> Value
toEncoding :: DateRange -> Encoding
$ctoEncoding :: DateRange -> Encoding
toJSON :: DateRange -> Value
$ctoJSON :: DateRange -> Value
parseJSONList :: Value -> Parser [DateRange]
$cparseJSONList :: Value -> Parser [DateRange]
parseJSON :: Value -> Parser DateRange
$cparseJSON :: Value -> Parser DateRange
toEncodingList :: [StatisticsValue] -> Encoding
$ctoEncodingList :: [StatisticsValue] -> Encoding
toJSONList :: [StatisticsValue] -> Value
$ctoJSONList :: [StatisticsValue] -> Value
toEncoding :: StatisticsValue -> Encoding
$ctoEncoding :: StatisticsValue -> Encoding
toJSON :: StatisticsValue -> Value
$ctoJSON :: StatisticsValue -> Value
parseJSONList :: Value -> Parser [StatisticsValue]
$cparseJSONList :: Value -> Parser [StatisticsValue]
parseJSON :: Value -> Parser StatisticsValue
$cparseJSON :: Value -> Parser StatisticsValue
toEncodingList :: [StatisticsGraph] -> Encoding
$ctoEncodingList :: [StatisticsGraph] -> Encoding
toJSONList :: [StatisticsGraph] -> Value
$ctoJSONList :: [StatisticsGraph] -> Value
toEncoding :: StatisticsGraph -> Encoding
$ctoEncoding :: StatisticsGraph -> Encoding
toJSON :: StatisticsGraph -> Value
$ctoJSON :: StatisticsGraph -> Value
parseJSONList :: Value -> Parser [StatisticsGraph]
$cparseJSONList :: Value -> Parser [StatisticsGraph]
parseJSON :: Value -> Parser StatisticsGraph
$cparseJSON :: Value -> Parser StatisticsGraph
toEncodingList :: [ChatStatisticsMessageInteractionCounters] -> Encoding
$ctoEncodingList :: [ChatStatisticsMessageInteractionCounters] -> Encoding
toJSONList :: [ChatStatisticsMessageInteractionCounters] -> Value
$ctoJSONList :: [ChatStatisticsMessageInteractionCounters] -> Value
toEncoding :: ChatStatisticsMessageInteractionCounters -> Encoding
$ctoEncoding :: ChatStatisticsMessageInteractionCounters -> Encoding
toJSON :: ChatStatisticsMessageInteractionCounters -> Value
$ctoJSON :: ChatStatisticsMessageInteractionCounters -> Value
parseJSONList :: Value -> Parser [ChatStatisticsMessageInteractionCounters]
$cparseJSONList :: Value -> Parser [ChatStatisticsMessageInteractionCounters]
parseJSON :: Value -> Parser ChatStatisticsMessageInteractionCounters
$cparseJSON :: Value -> Parser ChatStatisticsMessageInteractionCounters
toEncodingList :: [ChatStatistics] -> Encoding
$ctoEncodingList :: [ChatStatistics] -> Encoding
toJSONList :: [ChatStatistics] -> Value
$ctoJSONList :: [ChatStatistics] -> Value
toEncoding :: ChatStatistics -> Encoding
$ctoEncoding :: ChatStatistics -> Encoding
toJSON :: ChatStatistics -> Value
$ctoJSON :: ChatStatistics -> Value
parseJSONList :: Value -> Parser [ChatStatistics]
$cparseJSONList :: Value -> Parser [ChatStatistics]
parseJSON :: Value -> Parser ChatStatistics
$cparseJSON :: Value -> Parser ChatStatistics
toEncodingList :: [Update] -> Encoding
$ctoEncodingList :: [Update] -> Encoding
toJSONList :: [Update] -> Value
$ctoJSONList :: [Update] -> Value
toEncoding :: Update -> Encoding
$ctoEncoding :: Update -> Encoding
toJSON :: Update -> Value
$ctoJSON :: Update -> Value
parseJSONList :: Value -> Parser [Update]
$cparseJSONList :: Value -> Parser [Update]
parseJSON :: Value -> Parser Update
$cparseJSON :: Value -> Parser Update
toEncodingList :: [Updates] -> Encoding
$ctoEncodingList :: [Updates] -> Encoding
toJSONList :: [Updates] -> Value
$ctoJSONList :: [Updates] -> Value
toEncoding :: Updates -> Encoding
$ctoEncoding :: Updates -> Encoding
toJSON :: Updates -> Value
$ctoJSON :: Updates -> Value
parseJSONList :: Value -> Parser [Updates]
$cparseJSONList :: Value -> Parser [Updates]
parseJSON :: Value -> Parser Updates
$cparseJSON :: Value -> Parser Updates
toEncodingList :: [LogStream] -> Encoding
$ctoEncodingList :: [LogStream] -> Encoding
toJSONList :: [LogStream] -> Value
$ctoJSONList :: [LogStream] -> Value
toEncoding :: LogStream -> Encoding
$ctoEncoding :: LogStream -> Encoding
toJSON :: LogStream -> Value
$ctoJSON :: LogStream -> Value
parseJSONList :: Value -> Parser [LogStream]
$cparseJSONList :: Value -> Parser [LogStream]
parseJSON :: Value -> Parser LogStream
$cparseJSON :: Value -> Parser LogStream
toEncodingList :: [LogVerbosityLevel] -> Encoding
$ctoEncodingList :: [LogVerbosityLevel] -> Encoding
toJSONList :: [LogVerbosityLevel] -> Value
$ctoJSONList :: [LogVerbosityLevel] -> Value
toEncoding :: LogVerbosityLevel -> Encoding
$ctoEncoding :: LogVerbosityLevel -> Encoding
toJSON :: LogVerbosityLevel -> Value
$ctoJSON :: LogVerbosityLevel -> Value
parseJSONList :: Value -> Parser [LogVerbosityLevel]
$cparseJSONList :: Value -> Parser [LogVerbosityLevel]
parseJSON :: Value -> Parser LogVerbosityLevel
$cparseJSON :: Value -> Parser LogVerbosityLevel
toEncodingList :: [LogTags] -> Encoding
$ctoEncodingList :: [LogTags] -> Encoding
toJSONList :: [LogTags] -> Value
$ctoJSONList :: [LogTags] -> Value
toEncoding :: LogTags -> Encoding
$ctoEncoding :: LogTags -> Encoding
toJSON :: LogTags -> Value
$ctoJSON :: LogTags -> Value
parseJSONList :: Value -> Parser [LogTags]
$cparseJSONList :: Value -> Parser [LogTags]
parseJSON :: Value -> Parser LogTags
$cparseJSON :: Value -> Parser LogTags
toEncodingList :: [TestInt] -> Encoding
$ctoEncodingList :: [TestInt] -> Encoding
toJSONList :: [TestInt] -> Value
$ctoJSONList :: [TestInt] -> Value
toEncoding :: TestInt -> Encoding
$ctoEncoding :: TestInt -> Encoding
toJSON :: TestInt -> Value
$ctoJSON :: TestInt -> Value
parseJSONList :: Value -> Parser [TestInt]
$cparseJSONList :: Value -> Parser [TestInt]
parseJSON :: Value -> Parser TestInt
$cparseJSON :: Value -> Parser TestInt
toEncodingList :: [TestString] -> Encoding
$ctoEncodingList :: [TestString] -> Encoding
toJSONList :: [TestString] -> Value
$ctoJSONList :: [TestString] -> Value
toEncoding :: TestString -> Encoding
$ctoEncoding :: TestString -> Encoding
toJSON :: TestString -> Value
$ctoJSON :: TestString -> Value
parseJSONList :: Value -> Parser [TestString]
$cparseJSONList :: Value -> Parser [TestString]
parseJSON :: Value -> Parser TestString
$cparseJSON :: Value -> Parser TestString
toEncodingList :: [TestBytes] -> Encoding
$ctoEncodingList :: [TestBytes] -> Encoding
toJSONList :: [TestBytes] -> Value
$ctoJSONList :: [TestBytes] -> Value
toEncoding :: TestBytes -> Encoding
$ctoEncoding :: TestBytes -> Encoding
toJSON :: TestBytes -> Value
$ctoJSON :: TestBytes -> Value
parseJSONList :: Value -> Parser [TestBytes]
$cparseJSONList :: Value -> Parser [TestBytes]
parseJSON :: Value -> Parser TestBytes
$cparseJSON :: Value -> Parser TestBytes
toEncodingList :: [TestVectorInt] -> Encoding
$ctoEncodingList :: [TestVectorInt] -> Encoding
toJSONList :: [TestVectorInt] -> Value
$ctoJSONList :: [TestVectorInt] -> Value
toEncoding :: TestVectorInt -> Encoding
$ctoEncoding :: TestVectorInt -> Encoding
toJSON :: TestVectorInt -> Value
$ctoJSON :: TestVectorInt -> Value
parseJSONList :: Value -> Parser [TestVectorInt]
$cparseJSONList :: Value -> Parser [TestVectorInt]
parseJSON :: Value -> Parser TestVectorInt
$cparseJSON :: Value -> Parser TestVectorInt
toEncodingList :: [TestVectorIntObject] -> Encoding
$ctoEncodingList :: [TestVectorIntObject] -> Encoding
toJSONList :: [TestVectorIntObject] -> Value
$ctoJSONList :: [TestVectorIntObject] -> Value
toEncoding :: TestVectorIntObject -> Encoding
$ctoEncoding :: TestVectorIntObject -> Encoding
toJSON :: TestVectorIntObject -> Value
$ctoJSON :: TestVectorIntObject -> Value
parseJSONList :: Value -> Parser [TestVectorIntObject]
$cparseJSONList :: Value -> Parser [TestVectorIntObject]
parseJSON :: Value -> Parser TestVectorIntObject
$cparseJSON :: Value -> Parser TestVectorIntObject
toEncodingList :: [TestVectorString] -> Encoding
$ctoEncodingList :: [TestVectorString] -> Encoding
toJSONList :: [TestVectorString] -> Value
$ctoJSONList :: [TestVectorString] -> Value
toEncoding :: TestVectorString -> Encoding
$ctoEncoding :: TestVectorString -> Encoding
toJSON :: TestVectorString -> Value
$ctoJSON :: TestVectorString -> Value
parseJSONList :: Value -> Parser [TestVectorString]
$cparseJSONList :: Value -> Parser [TestVectorString]
parseJSON :: Value -> Parser TestVectorString
$cparseJSON :: Value -> Parser TestVectorString
toEncodingList :: [TestVectorStringObject] -> Encoding
$ctoEncodingList :: [TestVectorStringObject] -> Encoding
toJSONList :: [TestVectorStringObject] -> Value
$ctoJSONList :: [TestVectorStringObject] -> Value
toEncoding :: TestVectorStringObject -> Encoding
$ctoEncoding :: TestVectorStringObject -> Encoding
toJSON :: TestVectorStringObject -> Value
$ctoJSON :: TestVectorStringObject -> Value
parseJSONList :: Value -> Parser [TestVectorStringObject]
$cparseJSONList :: Value -> Parser [TestVectorStringObject]
parseJSON :: Value -> Parser TestVectorStringObject
$cparseJSON :: Value -> Parser TestVectorStringObject
instancesDec