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

-- | TD API function call arguments
module TDLib.Generated.FunArgs where

import Data.ByteString.Base64.Type
import GHC.Generics
import Language.Haskell.Codegen.TH
import Language.TL.I64
import TDLib.Generated.Types

-- | Parameter of Function getAuthorizationState
data GetAuthorizationState
  = -- | Returns the current authorization state; this is an offline request. For informational purposes only. Use updateAuthorizationState instead to maintain the current authorization state
    GetAuthorizationState
      {
      }
  deriving (Int -> GetAuthorizationState -> ShowS
[GetAuthorizationState] -> ShowS
GetAuthorizationState -> String
(Int -> GetAuthorizationState -> ShowS)
-> (GetAuthorizationState -> String)
-> ([GetAuthorizationState] -> ShowS)
-> Show GetAuthorizationState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAuthorizationState] -> ShowS
$cshowList :: [GetAuthorizationState] -> ShowS
show :: GetAuthorizationState -> String
$cshow :: GetAuthorizationState -> String
showsPrec :: Int -> GetAuthorizationState -> ShowS
$cshowsPrec :: Int -> GetAuthorizationState -> ShowS
Show, GetAuthorizationState -> GetAuthorizationState -> Bool
(GetAuthorizationState -> GetAuthorizationState -> Bool)
-> (GetAuthorizationState -> GetAuthorizationState -> Bool)
-> Eq GetAuthorizationState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAuthorizationState -> GetAuthorizationState -> Bool
$c/= :: GetAuthorizationState -> GetAuthorizationState -> Bool
== :: GetAuthorizationState -> GetAuthorizationState -> Bool
$c== :: GetAuthorizationState -> GetAuthorizationState -> Bool
Eq, (forall x. GetAuthorizationState -> Rep GetAuthorizationState x)
-> (forall x. Rep GetAuthorizationState x -> GetAuthorizationState)
-> Generic GetAuthorizationState
forall x. Rep GetAuthorizationState x -> GetAuthorizationState
forall x. GetAuthorizationState -> Rep GetAuthorizationState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAuthorizationState x -> GetAuthorizationState
$cfrom :: forall x. GetAuthorizationState -> Rep GetAuthorizationState x
Generic)

-- | Parameter of Function setTdlibParameters
data SetTdlibParameters
  = -- | Sets the parameters for TDLib initialization. Works only when the current authorization state is authorizationStateWaitTdlibParameters
    SetTdlibParameters
      { -- | Parameters
        SetTdlibParameters -> TdlibParameters
parameters :: TdlibParameters
      }
  deriving (Int -> SetTdlibParameters -> ShowS
[SetTdlibParameters] -> ShowS
SetTdlibParameters -> String
(Int -> SetTdlibParameters -> ShowS)
-> (SetTdlibParameters -> String)
-> ([SetTdlibParameters] -> ShowS)
-> Show SetTdlibParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetTdlibParameters] -> ShowS
$cshowList :: [SetTdlibParameters] -> ShowS
show :: SetTdlibParameters -> String
$cshow :: SetTdlibParameters -> String
showsPrec :: Int -> SetTdlibParameters -> ShowS
$cshowsPrec :: Int -> SetTdlibParameters -> ShowS
Show, SetTdlibParameters -> SetTdlibParameters -> Bool
(SetTdlibParameters -> SetTdlibParameters -> Bool)
-> (SetTdlibParameters -> SetTdlibParameters -> Bool)
-> Eq SetTdlibParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetTdlibParameters -> SetTdlibParameters -> Bool
$c/= :: SetTdlibParameters -> SetTdlibParameters -> Bool
== :: SetTdlibParameters -> SetTdlibParameters -> Bool
$c== :: SetTdlibParameters -> SetTdlibParameters -> Bool
Eq, (forall x. SetTdlibParameters -> Rep SetTdlibParameters x)
-> (forall x. Rep SetTdlibParameters x -> SetTdlibParameters)
-> Generic SetTdlibParameters
forall x. Rep SetTdlibParameters x -> SetTdlibParameters
forall x. SetTdlibParameters -> Rep SetTdlibParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetTdlibParameters x -> SetTdlibParameters
$cfrom :: forall x. SetTdlibParameters -> Rep SetTdlibParameters x
Generic)

-- | Parameter of Function checkDatabaseEncryptionKey
data CheckDatabaseEncryptionKey
  = -- | Checks the database encryption key for correctness. Works only when the current authorization state is authorizationStateWaitEncryptionKey
    CheckDatabaseEncryptionKey
      { -- | Encryption key to check or set up
        CheckDatabaseEncryptionKey -> ByteString64
encryption_key :: ByteString64
      }
  deriving (Int -> CheckDatabaseEncryptionKey -> ShowS
[CheckDatabaseEncryptionKey] -> ShowS
CheckDatabaseEncryptionKey -> String
(Int -> CheckDatabaseEncryptionKey -> ShowS)
-> (CheckDatabaseEncryptionKey -> String)
-> ([CheckDatabaseEncryptionKey] -> ShowS)
-> Show CheckDatabaseEncryptionKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckDatabaseEncryptionKey] -> ShowS
$cshowList :: [CheckDatabaseEncryptionKey] -> ShowS
show :: CheckDatabaseEncryptionKey -> String
$cshow :: CheckDatabaseEncryptionKey -> String
showsPrec :: Int -> CheckDatabaseEncryptionKey -> ShowS
$cshowsPrec :: Int -> CheckDatabaseEncryptionKey -> ShowS
Show, CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool
(CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool)
-> (CheckDatabaseEncryptionKey
    -> CheckDatabaseEncryptionKey -> Bool)
-> Eq CheckDatabaseEncryptionKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool
$c/= :: CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool
== :: CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool
$c== :: CheckDatabaseEncryptionKey -> CheckDatabaseEncryptionKey -> Bool
Eq, (forall x.
 CheckDatabaseEncryptionKey -> Rep CheckDatabaseEncryptionKey x)
-> (forall x.
    Rep CheckDatabaseEncryptionKey x -> CheckDatabaseEncryptionKey)
-> Generic CheckDatabaseEncryptionKey
forall x.
Rep CheckDatabaseEncryptionKey x -> CheckDatabaseEncryptionKey
forall x.
CheckDatabaseEncryptionKey -> Rep CheckDatabaseEncryptionKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckDatabaseEncryptionKey x -> CheckDatabaseEncryptionKey
$cfrom :: forall x.
CheckDatabaseEncryptionKey -> Rep CheckDatabaseEncryptionKey x
Generic)

-- | Parameter of Function setAuthenticationPhoneNumber
data SetAuthenticationPhoneNumber
  = -- | Sets the phone number of the user and sends an authentication code to the user. Works only when the current authorization state is authorizationStateWaitPhoneNumber,
    SetAuthenticationPhoneNumber
      { -- | The phone number of the user, in international format
        SetAuthenticationPhoneNumber -> T
phone_number :: T,
        -- | Settings for the authentication of the user's phone number
        SetAuthenticationPhoneNumber -> PhoneNumberAuthenticationSettings
settings :: PhoneNumberAuthenticationSettings
      }
  deriving (Int -> SetAuthenticationPhoneNumber -> ShowS
[SetAuthenticationPhoneNumber] -> ShowS
SetAuthenticationPhoneNumber -> String
(Int -> SetAuthenticationPhoneNumber -> ShowS)
-> (SetAuthenticationPhoneNumber -> String)
-> ([SetAuthenticationPhoneNumber] -> ShowS)
-> Show SetAuthenticationPhoneNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetAuthenticationPhoneNumber] -> ShowS
$cshowList :: [SetAuthenticationPhoneNumber] -> ShowS
show :: SetAuthenticationPhoneNumber -> String
$cshow :: SetAuthenticationPhoneNumber -> String
showsPrec :: Int -> SetAuthenticationPhoneNumber -> ShowS
$cshowsPrec :: Int -> SetAuthenticationPhoneNumber -> ShowS
Show, SetAuthenticationPhoneNumber
-> SetAuthenticationPhoneNumber -> Bool
(SetAuthenticationPhoneNumber
 -> SetAuthenticationPhoneNumber -> Bool)
-> (SetAuthenticationPhoneNumber
    -> SetAuthenticationPhoneNumber -> Bool)
-> Eq SetAuthenticationPhoneNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetAuthenticationPhoneNumber
-> SetAuthenticationPhoneNumber -> Bool
$c/= :: SetAuthenticationPhoneNumber
-> SetAuthenticationPhoneNumber -> Bool
== :: SetAuthenticationPhoneNumber
-> SetAuthenticationPhoneNumber -> Bool
$c== :: SetAuthenticationPhoneNumber
-> SetAuthenticationPhoneNumber -> Bool
Eq, (forall x.
 SetAuthenticationPhoneNumber -> Rep SetAuthenticationPhoneNumber x)
-> (forall x.
    Rep SetAuthenticationPhoneNumber x -> SetAuthenticationPhoneNumber)
-> Generic SetAuthenticationPhoneNumber
forall x.
Rep SetAuthenticationPhoneNumber x -> SetAuthenticationPhoneNumber
forall x.
SetAuthenticationPhoneNumber -> Rep SetAuthenticationPhoneNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetAuthenticationPhoneNumber x -> SetAuthenticationPhoneNumber
$cfrom :: forall x.
SetAuthenticationPhoneNumber -> Rep SetAuthenticationPhoneNumber x
Generic)

-- | Parameter of Function resendAuthenticationCode
data ResendAuthenticationCode
  = -- | Re-sends an authentication code to the user. Works only when the current authorization state is authorizationStateWaitCode and the next_code_type of the result is not null
    ResendAuthenticationCode
      {
      }
  deriving (Int -> ResendAuthenticationCode -> ShowS
[ResendAuthenticationCode] -> ShowS
ResendAuthenticationCode -> String
(Int -> ResendAuthenticationCode -> ShowS)
-> (ResendAuthenticationCode -> String)
-> ([ResendAuthenticationCode] -> ShowS)
-> Show ResendAuthenticationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendAuthenticationCode] -> ShowS
$cshowList :: [ResendAuthenticationCode] -> ShowS
show :: ResendAuthenticationCode -> String
$cshow :: ResendAuthenticationCode -> String
showsPrec :: Int -> ResendAuthenticationCode -> ShowS
$cshowsPrec :: Int -> ResendAuthenticationCode -> ShowS
Show, ResendAuthenticationCode -> ResendAuthenticationCode -> Bool
(ResendAuthenticationCode -> ResendAuthenticationCode -> Bool)
-> (ResendAuthenticationCode -> ResendAuthenticationCode -> Bool)
-> Eq ResendAuthenticationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendAuthenticationCode -> ResendAuthenticationCode -> Bool
$c/= :: ResendAuthenticationCode -> ResendAuthenticationCode -> Bool
== :: ResendAuthenticationCode -> ResendAuthenticationCode -> Bool
$c== :: ResendAuthenticationCode -> ResendAuthenticationCode -> Bool
Eq, (forall x.
 ResendAuthenticationCode -> Rep ResendAuthenticationCode x)
-> (forall x.
    Rep ResendAuthenticationCode x -> ResendAuthenticationCode)
-> Generic ResendAuthenticationCode
forall x.
Rep ResendAuthenticationCode x -> ResendAuthenticationCode
forall x.
ResendAuthenticationCode -> Rep ResendAuthenticationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendAuthenticationCode x -> ResendAuthenticationCode
$cfrom :: forall x.
ResendAuthenticationCode -> Rep ResendAuthenticationCode x
Generic)

-- | Parameter of Function checkAuthenticationCode
data CheckAuthenticationCode
  = -- | Checks the authentication code. Works only when the current authorization state is authorizationStateWaitCode
    CheckAuthenticationCode
      { -- | The verification code received via SMS, Telegram message, phone call, or flash call
        CheckAuthenticationCode -> T
code :: T
      }
  deriving (Int -> CheckAuthenticationCode -> ShowS
[CheckAuthenticationCode] -> ShowS
CheckAuthenticationCode -> String
(Int -> CheckAuthenticationCode -> ShowS)
-> (CheckAuthenticationCode -> String)
-> ([CheckAuthenticationCode] -> ShowS)
-> Show CheckAuthenticationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckAuthenticationCode] -> ShowS
$cshowList :: [CheckAuthenticationCode] -> ShowS
show :: CheckAuthenticationCode -> String
$cshow :: CheckAuthenticationCode -> String
showsPrec :: Int -> CheckAuthenticationCode -> ShowS
$cshowsPrec :: Int -> CheckAuthenticationCode -> ShowS
Show, CheckAuthenticationCode -> CheckAuthenticationCode -> Bool
(CheckAuthenticationCode -> CheckAuthenticationCode -> Bool)
-> (CheckAuthenticationCode -> CheckAuthenticationCode -> Bool)
-> Eq CheckAuthenticationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckAuthenticationCode -> CheckAuthenticationCode -> Bool
$c/= :: CheckAuthenticationCode -> CheckAuthenticationCode -> Bool
== :: CheckAuthenticationCode -> CheckAuthenticationCode -> Bool
$c== :: CheckAuthenticationCode -> CheckAuthenticationCode -> Bool
Eq, (forall x.
 CheckAuthenticationCode -> Rep CheckAuthenticationCode x)
-> (forall x.
    Rep CheckAuthenticationCode x -> CheckAuthenticationCode)
-> Generic CheckAuthenticationCode
forall x. Rep CheckAuthenticationCode x -> CheckAuthenticationCode
forall x. CheckAuthenticationCode -> Rep CheckAuthenticationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckAuthenticationCode x -> CheckAuthenticationCode
$cfrom :: forall x. CheckAuthenticationCode -> Rep CheckAuthenticationCode x
Generic)

-- | Parameter of Function requestQrCodeAuthentication
data RequestQrCodeAuthentication
  = -- | Requests QR code authentication by scanning a QR code on another logged in device. Works only when the current authorization state is authorizationStateWaitPhoneNumber
    RequestQrCodeAuthentication
      { -- | List of user identifiers of other users currently using the client
        RequestQrCodeAuthentication -> [Int]
other_user_ids :: ([]) (I32)
      }
  deriving (Int -> RequestQrCodeAuthentication -> ShowS
[RequestQrCodeAuthentication] -> ShowS
RequestQrCodeAuthentication -> String
(Int -> RequestQrCodeAuthentication -> ShowS)
-> (RequestQrCodeAuthentication -> String)
-> ([RequestQrCodeAuthentication] -> ShowS)
-> Show RequestQrCodeAuthentication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestQrCodeAuthentication] -> ShowS
$cshowList :: [RequestQrCodeAuthentication] -> ShowS
show :: RequestQrCodeAuthentication -> String
$cshow :: RequestQrCodeAuthentication -> String
showsPrec :: Int -> RequestQrCodeAuthentication -> ShowS
$cshowsPrec :: Int -> RequestQrCodeAuthentication -> ShowS
Show, RequestQrCodeAuthentication -> RequestQrCodeAuthentication -> Bool
(RequestQrCodeAuthentication
 -> RequestQrCodeAuthentication -> Bool)
-> (RequestQrCodeAuthentication
    -> RequestQrCodeAuthentication -> Bool)
-> Eq RequestQrCodeAuthentication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestQrCodeAuthentication -> RequestQrCodeAuthentication -> Bool
$c/= :: RequestQrCodeAuthentication -> RequestQrCodeAuthentication -> Bool
== :: RequestQrCodeAuthentication -> RequestQrCodeAuthentication -> Bool
$c== :: RequestQrCodeAuthentication -> RequestQrCodeAuthentication -> Bool
Eq, (forall x.
 RequestQrCodeAuthentication -> Rep RequestQrCodeAuthentication x)
-> (forall x.
    Rep RequestQrCodeAuthentication x -> RequestQrCodeAuthentication)
-> Generic RequestQrCodeAuthentication
forall x.
Rep RequestQrCodeAuthentication x -> RequestQrCodeAuthentication
forall x.
RequestQrCodeAuthentication -> Rep RequestQrCodeAuthentication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RequestQrCodeAuthentication x -> RequestQrCodeAuthentication
$cfrom :: forall x.
RequestQrCodeAuthentication -> Rep RequestQrCodeAuthentication x
Generic)

-- | Parameter of Function registerUser
data RegisterUser
  = -- | Finishes user registration. Works only when the current authorization state is authorizationStateWaitRegistration
    RegisterUser
      { -- | The first name of the user; 1-64 characters
        RegisterUser -> T
first_name :: T,
        -- | The last name of the user; 0-64 characters
        RegisterUser -> T
last_name :: T
      }
  deriving (Int -> RegisterUser -> ShowS
[RegisterUser] -> ShowS
RegisterUser -> String
(Int -> RegisterUser -> ShowS)
-> (RegisterUser -> String)
-> ([RegisterUser] -> ShowS)
-> Show RegisterUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterUser] -> ShowS
$cshowList :: [RegisterUser] -> ShowS
show :: RegisterUser -> String
$cshow :: RegisterUser -> String
showsPrec :: Int -> RegisterUser -> ShowS
$cshowsPrec :: Int -> RegisterUser -> ShowS
Show, RegisterUser -> RegisterUser -> Bool
(RegisterUser -> RegisterUser -> Bool)
-> (RegisterUser -> RegisterUser -> Bool) -> Eq RegisterUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterUser -> RegisterUser -> Bool
$c/= :: RegisterUser -> RegisterUser -> Bool
== :: RegisterUser -> RegisterUser -> Bool
$c== :: RegisterUser -> RegisterUser -> Bool
Eq, (forall x. RegisterUser -> Rep RegisterUser x)
-> (forall x. Rep RegisterUser x -> RegisterUser)
-> Generic RegisterUser
forall x. Rep RegisterUser x -> RegisterUser
forall x. RegisterUser -> Rep RegisterUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterUser x -> RegisterUser
$cfrom :: forall x. RegisterUser -> Rep RegisterUser x
Generic)

-- | Parameter of Function checkAuthenticationPassword
data CheckAuthenticationPassword
  = -- | Checks the authentication password for correctness. Works only when the current authorization state is authorizationStateWaitPassword
    CheckAuthenticationPassword
      { -- | The password to check
        CheckAuthenticationPassword -> T
password :: T
      }
  deriving (Int -> CheckAuthenticationPassword -> ShowS
[CheckAuthenticationPassword] -> ShowS
CheckAuthenticationPassword -> String
(Int -> CheckAuthenticationPassword -> ShowS)
-> (CheckAuthenticationPassword -> String)
-> ([CheckAuthenticationPassword] -> ShowS)
-> Show CheckAuthenticationPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckAuthenticationPassword] -> ShowS
$cshowList :: [CheckAuthenticationPassword] -> ShowS
show :: CheckAuthenticationPassword -> String
$cshow :: CheckAuthenticationPassword -> String
showsPrec :: Int -> CheckAuthenticationPassword -> ShowS
$cshowsPrec :: Int -> CheckAuthenticationPassword -> ShowS
Show, CheckAuthenticationPassword -> CheckAuthenticationPassword -> Bool
(CheckAuthenticationPassword
 -> CheckAuthenticationPassword -> Bool)
-> (CheckAuthenticationPassword
    -> CheckAuthenticationPassword -> Bool)
-> Eq CheckAuthenticationPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckAuthenticationPassword -> CheckAuthenticationPassword -> Bool
$c/= :: CheckAuthenticationPassword -> CheckAuthenticationPassword -> Bool
== :: CheckAuthenticationPassword -> CheckAuthenticationPassword -> Bool
$c== :: CheckAuthenticationPassword -> CheckAuthenticationPassword -> Bool
Eq, (forall x.
 CheckAuthenticationPassword -> Rep CheckAuthenticationPassword x)
-> (forall x.
    Rep CheckAuthenticationPassword x -> CheckAuthenticationPassword)
-> Generic CheckAuthenticationPassword
forall x.
Rep CheckAuthenticationPassword x -> CheckAuthenticationPassword
forall x.
CheckAuthenticationPassword -> Rep CheckAuthenticationPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckAuthenticationPassword x -> CheckAuthenticationPassword
$cfrom :: forall x.
CheckAuthenticationPassword -> Rep CheckAuthenticationPassword x
Generic)

-- | Parameter of Function requestAuthenticationPasswordRecovery
data RequestAuthenticationPasswordRecovery
  = -- | Requests to send a password recovery code to an email address that was previously set up. Works only when the current authorization state is authorizationStateWaitPassword
    RequestAuthenticationPasswordRecovery
      {
      }
  deriving (Int -> RequestAuthenticationPasswordRecovery -> ShowS
[RequestAuthenticationPasswordRecovery] -> ShowS
RequestAuthenticationPasswordRecovery -> String
(Int -> RequestAuthenticationPasswordRecovery -> ShowS)
-> (RequestAuthenticationPasswordRecovery -> String)
-> ([RequestAuthenticationPasswordRecovery] -> ShowS)
-> Show RequestAuthenticationPasswordRecovery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestAuthenticationPasswordRecovery] -> ShowS
$cshowList :: [RequestAuthenticationPasswordRecovery] -> ShowS
show :: RequestAuthenticationPasswordRecovery -> String
$cshow :: RequestAuthenticationPasswordRecovery -> String
showsPrec :: Int -> RequestAuthenticationPasswordRecovery -> ShowS
$cshowsPrec :: Int -> RequestAuthenticationPasswordRecovery -> ShowS
Show, RequestAuthenticationPasswordRecovery
-> RequestAuthenticationPasswordRecovery -> Bool
(RequestAuthenticationPasswordRecovery
 -> RequestAuthenticationPasswordRecovery -> Bool)
-> (RequestAuthenticationPasswordRecovery
    -> RequestAuthenticationPasswordRecovery -> Bool)
-> Eq RequestAuthenticationPasswordRecovery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestAuthenticationPasswordRecovery
-> RequestAuthenticationPasswordRecovery -> Bool
$c/= :: RequestAuthenticationPasswordRecovery
-> RequestAuthenticationPasswordRecovery -> Bool
== :: RequestAuthenticationPasswordRecovery
-> RequestAuthenticationPasswordRecovery -> Bool
$c== :: RequestAuthenticationPasswordRecovery
-> RequestAuthenticationPasswordRecovery -> Bool
Eq, (forall x.
 RequestAuthenticationPasswordRecovery
 -> Rep RequestAuthenticationPasswordRecovery x)
-> (forall x.
    Rep RequestAuthenticationPasswordRecovery x
    -> RequestAuthenticationPasswordRecovery)
-> Generic RequestAuthenticationPasswordRecovery
forall x.
Rep RequestAuthenticationPasswordRecovery x
-> RequestAuthenticationPasswordRecovery
forall x.
RequestAuthenticationPasswordRecovery
-> Rep RequestAuthenticationPasswordRecovery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RequestAuthenticationPasswordRecovery x
-> RequestAuthenticationPasswordRecovery
$cfrom :: forall x.
RequestAuthenticationPasswordRecovery
-> Rep RequestAuthenticationPasswordRecovery x
Generic)

-- | Parameter of Function recoverAuthenticationPassword
data RecoverAuthenticationPassword
  = -- | Recovers the password with a password recovery code sent to an email address that was previously set up. Works only when the current authorization state is authorizationStateWaitPassword
    RecoverAuthenticationPassword
      { -- | Recovery code to check
        RecoverAuthenticationPassword -> T
recovery_code :: T
      }
  deriving (Int -> RecoverAuthenticationPassword -> ShowS
[RecoverAuthenticationPassword] -> ShowS
RecoverAuthenticationPassword -> String
(Int -> RecoverAuthenticationPassword -> ShowS)
-> (RecoverAuthenticationPassword -> String)
-> ([RecoverAuthenticationPassword] -> ShowS)
-> Show RecoverAuthenticationPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoverAuthenticationPassword] -> ShowS
$cshowList :: [RecoverAuthenticationPassword] -> ShowS
show :: RecoverAuthenticationPassword -> String
$cshow :: RecoverAuthenticationPassword -> String
showsPrec :: Int -> RecoverAuthenticationPassword -> ShowS
$cshowsPrec :: Int -> RecoverAuthenticationPassword -> ShowS
Show, RecoverAuthenticationPassword
-> RecoverAuthenticationPassword -> Bool
(RecoverAuthenticationPassword
 -> RecoverAuthenticationPassword -> Bool)
-> (RecoverAuthenticationPassword
    -> RecoverAuthenticationPassword -> Bool)
-> Eq RecoverAuthenticationPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoverAuthenticationPassword
-> RecoverAuthenticationPassword -> Bool
$c/= :: RecoverAuthenticationPassword
-> RecoverAuthenticationPassword -> Bool
== :: RecoverAuthenticationPassword
-> RecoverAuthenticationPassword -> Bool
$c== :: RecoverAuthenticationPassword
-> RecoverAuthenticationPassword -> Bool
Eq, (forall x.
 RecoverAuthenticationPassword
 -> Rep RecoverAuthenticationPassword x)
-> (forall x.
    Rep RecoverAuthenticationPassword x
    -> RecoverAuthenticationPassword)
-> Generic RecoverAuthenticationPassword
forall x.
Rep RecoverAuthenticationPassword x
-> RecoverAuthenticationPassword
forall x.
RecoverAuthenticationPassword
-> Rep RecoverAuthenticationPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RecoverAuthenticationPassword x
-> RecoverAuthenticationPassword
$cfrom :: forall x.
RecoverAuthenticationPassword
-> Rep RecoverAuthenticationPassword x
Generic)

-- | Parameter of Function checkAuthenticationBotToken
data CheckAuthenticationBotToken
  = -- | Checks the authentication token of a bot; to log in as a bot. Works only when the current authorization state is authorizationStateWaitPhoneNumber. Can be used instead of setAuthenticationPhoneNumber and checkAuthenticationCode to log in
    CheckAuthenticationBotToken
      { -- | The bot token
        CheckAuthenticationBotToken -> T
token :: T
      }
  deriving (Int -> CheckAuthenticationBotToken -> ShowS
[CheckAuthenticationBotToken] -> ShowS
CheckAuthenticationBotToken -> String
(Int -> CheckAuthenticationBotToken -> ShowS)
-> (CheckAuthenticationBotToken -> String)
-> ([CheckAuthenticationBotToken] -> ShowS)
-> Show CheckAuthenticationBotToken
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckAuthenticationBotToken] -> ShowS
$cshowList :: [CheckAuthenticationBotToken] -> ShowS
show :: CheckAuthenticationBotToken -> String
$cshow :: CheckAuthenticationBotToken -> String
showsPrec :: Int -> CheckAuthenticationBotToken -> ShowS
$cshowsPrec :: Int -> CheckAuthenticationBotToken -> ShowS
Show, CheckAuthenticationBotToken -> CheckAuthenticationBotToken -> Bool
(CheckAuthenticationBotToken
 -> CheckAuthenticationBotToken -> Bool)
-> (CheckAuthenticationBotToken
    -> CheckAuthenticationBotToken -> Bool)
-> Eq CheckAuthenticationBotToken
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckAuthenticationBotToken -> CheckAuthenticationBotToken -> Bool
$c/= :: CheckAuthenticationBotToken -> CheckAuthenticationBotToken -> Bool
== :: CheckAuthenticationBotToken -> CheckAuthenticationBotToken -> Bool
$c== :: CheckAuthenticationBotToken -> CheckAuthenticationBotToken -> Bool
Eq, (forall x.
 CheckAuthenticationBotToken -> Rep CheckAuthenticationBotToken x)
-> (forall x.
    Rep CheckAuthenticationBotToken x -> CheckAuthenticationBotToken)
-> Generic CheckAuthenticationBotToken
forall x.
Rep CheckAuthenticationBotToken x -> CheckAuthenticationBotToken
forall x.
CheckAuthenticationBotToken -> Rep CheckAuthenticationBotToken x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckAuthenticationBotToken x -> CheckAuthenticationBotToken
$cfrom :: forall x.
CheckAuthenticationBotToken -> Rep CheckAuthenticationBotToken x
Generic)

-- | Parameter of Function logOut
data LogOut
  = -- | Closes the TDLib instance after a proper logout. Requires an available network connection. All local data will be destroyed. After the logout completes, updateAuthorizationState with authorizationStateClosed will be sent
    LogOut
      {
      }
  deriving (Int -> LogOut -> ShowS
[LogOut] -> ShowS
LogOut -> String
(Int -> LogOut -> ShowS)
-> (LogOut -> String) -> ([LogOut] -> ShowS) -> Show LogOut
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LogOut] -> ShowS
$cshowList :: [LogOut] -> ShowS
show :: LogOut -> String
$cshow :: LogOut -> String
showsPrec :: Int -> LogOut -> ShowS
$cshowsPrec :: Int -> LogOut -> ShowS
Show, LogOut -> LogOut -> Bool
(LogOut -> LogOut -> Bool)
-> (LogOut -> LogOut -> Bool) -> Eq LogOut
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LogOut -> LogOut -> Bool
$c/= :: LogOut -> LogOut -> Bool
== :: LogOut -> LogOut -> Bool
$c== :: LogOut -> LogOut -> Bool
Eq, (forall x. LogOut -> Rep LogOut x)
-> (forall x. Rep LogOut x -> LogOut) -> Generic LogOut
forall x. Rep LogOut x -> LogOut
forall x. LogOut -> Rep LogOut x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LogOut x -> LogOut
$cfrom :: forall x. LogOut -> Rep LogOut x
Generic)

-- | Parameter of Function close
data Close
  = -- | Closes the TDLib instance. All databases will be flushed to disk and properly closed. After the close completes, updateAuthorizationState with authorizationStateClosed will be sent
    Close
      {
      }
  deriving (Int -> Close -> ShowS
[Close] -> ShowS
Close -> String
(Int -> Close -> ShowS)
-> (Close -> String) -> ([Close] -> ShowS) -> Show Close
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Close] -> ShowS
$cshowList :: [Close] -> ShowS
show :: Close -> String
$cshow :: Close -> String
showsPrec :: Int -> Close -> ShowS
$cshowsPrec :: Int -> Close -> ShowS
Show, Close -> Close -> Bool
(Close -> Close -> Bool) -> (Close -> Close -> Bool) -> Eq Close
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Close -> Close -> Bool
$c/= :: Close -> Close -> Bool
== :: Close -> Close -> Bool
$c== :: Close -> Close -> Bool
Eq, (forall x. Close -> Rep Close x)
-> (forall x. Rep Close x -> Close) -> Generic Close
forall x. Rep Close x -> Close
forall x. Close -> Rep Close x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Close x -> Close
$cfrom :: forall x. Close -> Rep Close x
Generic)

-- | Parameter of Function destroy
data Destroy
  = -- | Closes the TDLib instance, destroying all local data without a proper logout. The current user session will remain in the list of all active sessions. All local data will be destroyed. After the destruction completes updateAuthorizationState with authorizationStateClosed will be sent
    Destroy
      {
      }
  deriving (Int -> Destroy -> ShowS
[Destroy] -> ShowS
Destroy -> String
(Int -> Destroy -> ShowS)
-> (Destroy -> String) -> ([Destroy] -> ShowS) -> Show Destroy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Destroy] -> ShowS
$cshowList :: [Destroy] -> ShowS
show :: Destroy -> String
$cshow :: Destroy -> String
showsPrec :: Int -> Destroy -> ShowS
$cshowsPrec :: Int -> Destroy -> ShowS
Show, Destroy -> Destroy -> Bool
(Destroy -> Destroy -> Bool)
-> (Destroy -> Destroy -> Bool) -> Eq Destroy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Destroy -> Destroy -> Bool
$c/= :: Destroy -> Destroy -> Bool
== :: Destroy -> Destroy -> Bool
$c== :: Destroy -> Destroy -> Bool
Eq, (forall x. Destroy -> Rep Destroy x)
-> (forall x. Rep Destroy x -> Destroy) -> Generic Destroy
forall x. Rep Destroy x -> Destroy
forall x. Destroy -> Rep Destroy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Destroy x -> Destroy
$cfrom :: forall x. Destroy -> Rep Destroy x
Generic)

-- | Parameter of Function confirmQrCodeAuthentication
data ConfirmQrCodeAuthentication
  = -- | Confirms QR code authentication on another device. Returns created session on success
    ConfirmQrCodeAuthentication
      { -- | A link from a QR code. The link must be scanned by the in-app camera
        ConfirmQrCodeAuthentication -> T
link :: T
      }
  deriving (Int -> ConfirmQrCodeAuthentication -> ShowS
[ConfirmQrCodeAuthentication] -> ShowS
ConfirmQrCodeAuthentication -> String
(Int -> ConfirmQrCodeAuthentication -> ShowS)
-> (ConfirmQrCodeAuthentication -> String)
-> ([ConfirmQrCodeAuthentication] -> ShowS)
-> Show ConfirmQrCodeAuthentication
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ConfirmQrCodeAuthentication] -> ShowS
$cshowList :: [ConfirmQrCodeAuthentication] -> ShowS
show :: ConfirmQrCodeAuthentication -> String
$cshow :: ConfirmQrCodeAuthentication -> String
showsPrec :: Int -> ConfirmQrCodeAuthentication -> ShowS
$cshowsPrec :: Int -> ConfirmQrCodeAuthentication -> ShowS
Show, ConfirmQrCodeAuthentication -> ConfirmQrCodeAuthentication -> Bool
(ConfirmQrCodeAuthentication
 -> ConfirmQrCodeAuthentication -> Bool)
-> (ConfirmQrCodeAuthentication
    -> ConfirmQrCodeAuthentication -> Bool)
-> Eq ConfirmQrCodeAuthentication
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConfirmQrCodeAuthentication -> ConfirmQrCodeAuthentication -> Bool
$c/= :: ConfirmQrCodeAuthentication -> ConfirmQrCodeAuthentication -> Bool
== :: ConfirmQrCodeAuthentication -> ConfirmQrCodeAuthentication -> Bool
$c== :: ConfirmQrCodeAuthentication -> ConfirmQrCodeAuthentication -> Bool
Eq, (forall x.
 ConfirmQrCodeAuthentication -> Rep ConfirmQrCodeAuthentication x)
-> (forall x.
    Rep ConfirmQrCodeAuthentication x -> ConfirmQrCodeAuthentication)
-> Generic ConfirmQrCodeAuthentication
forall x.
Rep ConfirmQrCodeAuthentication x -> ConfirmQrCodeAuthentication
forall x.
ConfirmQrCodeAuthentication -> Rep ConfirmQrCodeAuthentication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ConfirmQrCodeAuthentication x -> ConfirmQrCodeAuthentication
$cfrom :: forall x.
ConfirmQrCodeAuthentication -> Rep ConfirmQrCodeAuthentication x
Generic)

-- | Parameter of Function getCurrentState
data GetCurrentState
  = -- | Returns all updates needed to restore current TDLib state, i.e. all actual UpdateAuthorizationState/UpdateUser/UpdateNewChat and others. This is especially useful if TDLib is run in a separate process. This is an offline method. Can be called before authorization
    GetCurrentState
      {
      }
  deriving (Int -> GetCurrentState -> ShowS
[GetCurrentState] -> ShowS
GetCurrentState -> String
(Int -> GetCurrentState -> ShowS)
-> (GetCurrentState -> String)
-> ([GetCurrentState] -> ShowS)
-> Show GetCurrentState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCurrentState] -> ShowS
$cshowList :: [GetCurrentState] -> ShowS
show :: GetCurrentState -> String
$cshow :: GetCurrentState -> String
showsPrec :: Int -> GetCurrentState -> ShowS
$cshowsPrec :: Int -> GetCurrentState -> ShowS
Show, GetCurrentState -> GetCurrentState -> Bool
(GetCurrentState -> GetCurrentState -> Bool)
-> (GetCurrentState -> GetCurrentState -> Bool)
-> Eq GetCurrentState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCurrentState -> GetCurrentState -> Bool
$c/= :: GetCurrentState -> GetCurrentState -> Bool
== :: GetCurrentState -> GetCurrentState -> Bool
$c== :: GetCurrentState -> GetCurrentState -> Bool
Eq, (forall x. GetCurrentState -> Rep GetCurrentState x)
-> (forall x. Rep GetCurrentState x -> GetCurrentState)
-> Generic GetCurrentState
forall x. Rep GetCurrentState x -> GetCurrentState
forall x. GetCurrentState -> Rep GetCurrentState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCurrentState x -> GetCurrentState
$cfrom :: forall x. GetCurrentState -> Rep GetCurrentState x
Generic)

-- | Parameter of Function setDatabaseEncryptionKey
data SetDatabaseEncryptionKey
  = -- | Changes the database encryption key. Usually the encryption key is never changed and is stored in some OS keychain
    SetDatabaseEncryptionKey
      { -- | New encryption key
        SetDatabaseEncryptionKey -> ByteString64
new_encryption_key :: ByteString64
      }
  deriving (Int -> SetDatabaseEncryptionKey -> ShowS
[SetDatabaseEncryptionKey] -> ShowS
SetDatabaseEncryptionKey -> String
(Int -> SetDatabaseEncryptionKey -> ShowS)
-> (SetDatabaseEncryptionKey -> String)
-> ([SetDatabaseEncryptionKey] -> ShowS)
-> Show SetDatabaseEncryptionKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetDatabaseEncryptionKey] -> ShowS
$cshowList :: [SetDatabaseEncryptionKey] -> ShowS
show :: SetDatabaseEncryptionKey -> String
$cshow :: SetDatabaseEncryptionKey -> String
showsPrec :: Int -> SetDatabaseEncryptionKey -> ShowS
$cshowsPrec :: Int -> SetDatabaseEncryptionKey -> ShowS
Show, SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool
(SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool)
-> (SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool)
-> Eq SetDatabaseEncryptionKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool
$c/= :: SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool
== :: SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool
$c== :: SetDatabaseEncryptionKey -> SetDatabaseEncryptionKey -> Bool
Eq, (forall x.
 SetDatabaseEncryptionKey -> Rep SetDatabaseEncryptionKey x)
-> (forall x.
    Rep SetDatabaseEncryptionKey x -> SetDatabaseEncryptionKey)
-> Generic SetDatabaseEncryptionKey
forall x.
Rep SetDatabaseEncryptionKey x -> SetDatabaseEncryptionKey
forall x.
SetDatabaseEncryptionKey -> Rep SetDatabaseEncryptionKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetDatabaseEncryptionKey x -> SetDatabaseEncryptionKey
$cfrom :: forall x.
SetDatabaseEncryptionKey -> Rep SetDatabaseEncryptionKey x
Generic)

-- | Parameter of Function getPasswordState
data GetPasswordState
  = -- | Returns the current state of 2-step verification
    GetPasswordState
      {
      }
  deriving (Int -> GetPasswordState -> ShowS
[GetPasswordState] -> ShowS
GetPasswordState -> String
(Int -> GetPasswordState -> ShowS)
-> (GetPasswordState -> String)
-> ([GetPasswordState] -> ShowS)
-> Show GetPasswordState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPasswordState] -> ShowS
$cshowList :: [GetPasswordState] -> ShowS
show :: GetPasswordState -> String
$cshow :: GetPasswordState -> String
showsPrec :: Int -> GetPasswordState -> ShowS
$cshowsPrec :: Int -> GetPasswordState -> ShowS
Show, GetPasswordState -> GetPasswordState -> Bool
(GetPasswordState -> GetPasswordState -> Bool)
-> (GetPasswordState -> GetPasswordState -> Bool)
-> Eq GetPasswordState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPasswordState -> GetPasswordState -> Bool
$c/= :: GetPasswordState -> GetPasswordState -> Bool
== :: GetPasswordState -> GetPasswordState -> Bool
$c== :: GetPasswordState -> GetPasswordState -> Bool
Eq, (forall x. GetPasswordState -> Rep GetPasswordState x)
-> (forall x. Rep GetPasswordState x -> GetPasswordState)
-> Generic GetPasswordState
forall x. Rep GetPasswordState x -> GetPasswordState
forall x. GetPasswordState -> Rep GetPasswordState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPasswordState x -> GetPasswordState
$cfrom :: forall x. GetPasswordState -> Rep GetPasswordState x
Generic)

-- | Parameter of Function setPassword
data SetPassword
  = -- | Changes the password for the user. If a new recovery email address is specified, then the change will not be applied until the new recovery email address is confirmed
    SetPassword
      { -- | Previous password of the user
        SetPassword -> T
old_password :: T,
        -- | New password of the user; may be empty to remove the password
        SetPassword -> T
new_password :: T,
        -- | New password hint; may be empty
        SetPassword -> T
new_hint :: T,
        -- | Pass true if the recovery email address should be changed
        SetPassword -> Bool
set_recovery_email_address :: Bool,
        -- | New recovery email address; may be empty
        SetPassword -> T
new_recovery_email_address :: T
      }
  deriving (Int -> SetPassword -> ShowS
[SetPassword] -> ShowS
SetPassword -> String
(Int -> SetPassword -> ShowS)
-> (SetPassword -> String)
-> ([SetPassword] -> ShowS)
-> Show SetPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPassword] -> ShowS
$cshowList :: [SetPassword] -> ShowS
show :: SetPassword -> String
$cshow :: SetPassword -> String
showsPrec :: Int -> SetPassword -> ShowS
$cshowsPrec :: Int -> SetPassword -> ShowS
Show, SetPassword -> SetPassword -> Bool
(SetPassword -> SetPassword -> Bool)
-> (SetPassword -> SetPassword -> Bool) -> Eq SetPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPassword -> SetPassword -> Bool
$c/= :: SetPassword -> SetPassword -> Bool
== :: SetPassword -> SetPassword -> Bool
$c== :: SetPassword -> SetPassword -> Bool
Eq, (forall x. SetPassword -> Rep SetPassword x)
-> (forall x. Rep SetPassword x -> SetPassword)
-> Generic SetPassword
forall x. Rep SetPassword x -> SetPassword
forall x. SetPassword -> Rep SetPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetPassword x -> SetPassword
$cfrom :: forall x. SetPassword -> Rep SetPassword x
Generic)

-- | Parameter of Function getRecoveryEmailAddress
data GetRecoveryEmailAddress
  = -- | Returns a 2-step verification recovery email address that was previously set up. This method can be used to verify a password provided by the user
    GetRecoveryEmailAddress
      { -- | The password for the current user
        GetRecoveryEmailAddress -> T
password :: T
      }
  deriving (Int -> GetRecoveryEmailAddress -> ShowS
[GetRecoveryEmailAddress] -> ShowS
GetRecoveryEmailAddress -> String
(Int -> GetRecoveryEmailAddress -> ShowS)
-> (GetRecoveryEmailAddress -> String)
-> ([GetRecoveryEmailAddress] -> ShowS)
-> Show GetRecoveryEmailAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecoveryEmailAddress] -> ShowS
$cshowList :: [GetRecoveryEmailAddress] -> ShowS
show :: GetRecoveryEmailAddress -> String
$cshow :: GetRecoveryEmailAddress -> String
showsPrec :: Int -> GetRecoveryEmailAddress -> ShowS
$cshowsPrec :: Int -> GetRecoveryEmailAddress -> ShowS
Show, GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool
(GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool)
-> (GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool)
-> Eq GetRecoveryEmailAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool
$c/= :: GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool
== :: GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool
$c== :: GetRecoveryEmailAddress -> GetRecoveryEmailAddress -> Bool
Eq, (forall x.
 GetRecoveryEmailAddress -> Rep GetRecoveryEmailAddress x)
-> (forall x.
    Rep GetRecoveryEmailAddress x -> GetRecoveryEmailAddress)
-> Generic GetRecoveryEmailAddress
forall x. Rep GetRecoveryEmailAddress x -> GetRecoveryEmailAddress
forall x. GetRecoveryEmailAddress -> Rep GetRecoveryEmailAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRecoveryEmailAddress x -> GetRecoveryEmailAddress
$cfrom :: forall x. GetRecoveryEmailAddress -> Rep GetRecoveryEmailAddress x
Generic)

-- | Parameter of Function setRecoveryEmailAddress
data SetRecoveryEmailAddress
  = -- | Changes the 2-step verification recovery email address of the user. If a new recovery email address is specified, then the change will not be applied until the new recovery email address is confirmed.
    SetRecoveryEmailAddress
      { SetRecoveryEmailAddress -> T
password :: T,
        SetRecoveryEmailAddress -> T
new_recovery_email_address :: T
      }
  deriving (Int -> SetRecoveryEmailAddress -> ShowS
[SetRecoveryEmailAddress] -> ShowS
SetRecoveryEmailAddress -> String
(Int -> SetRecoveryEmailAddress -> ShowS)
-> (SetRecoveryEmailAddress -> String)
-> ([SetRecoveryEmailAddress] -> ShowS)
-> Show SetRecoveryEmailAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetRecoveryEmailAddress] -> ShowS
$cshowList :: [SetRecoveryEmailAddress] -> ShowS
show :: SetRecoveryEmailAddress -> String
$cshow :: SetRecoveryEmailAddress -> String
showsPrec :: Int -> SetRecoveryEmailAddress -> ShowS
$cshowsPrec :: Int -> SetRecoveryEmailAddress -> ShowS
Show, SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool
(SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool)
-> (SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool)
-> Eq SetRecoveryEmailAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool
$c/= :: SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool
== :: SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool
$c== :: SetRecoveryEmailAddress -> SetRecoveryEmailAddress -> Bool
Eq, (forall x.
 SetRecoveryEmailAddress -> Rep SetRecoveryEmailAddress x)
-> (forall x.
    Rep SetRecoveryEmailAddress x -> SetRecoveryEmailAddress)
-> Generic SetRecoveryEmailAddress
forall x. Rep SetRecoveryEmailAddress x -> SetRecoveryEmailAddress
forall x. SetRecoveryEmailAddress -> Rep SetRecoveryEmailAddress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetRecoveryEmailAddress x -> SetRecoveryEmailAddress
$cfrom :: forall x. SetRecoveryEmailAddress -> Rep SetRecoveryEmailAddress x
Generic)

-- | Parameter of Function checkRecoveryEmailAddressCode
data CheckRecoveryEmailAddressCode
  = -- | Checks the 2-step verification recovery email address verification code
    CheckRecoveryEmailAddressCode
      { -- | Verification code
        CheckRecoveryEmailAddressCode -> T
code :: T
      }
  deriving (Int -> CheckRecoveryEmailAddressCode -> ShowS
[CheckRecoveryEmailAddressCode] -> ShowS
CheckRecoveryEmailAddressCode -> String
(Int -> CheckRecoveryEmailAddressCode -> ShowS)
-> (CheckRecoveryEmailAddressCode -> String)
-> ([CheckRecoveryEmailAddressCode] -> ShowS)
-> Show CheckRecoveryEmailAddressCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckRecoveryEmailAddressCode] -> ShowS
$cshowList :: [CheckRecoveryEmailAddressCode] -> ShowS
show :: CheckRecoveryEmailAddressCode -> String
$cshow :: CheckRecoveryEmailAddressCode -> String
showsPrec :: Int -> CheckRecoveryEmailAddressCode -> ShowS
$cshowsPrec :: Int -> CheckRecoveryEmailAddressCode -> ShowS
Show, CheckRecoveryEmailAddressCode
-> CheckRecoveryEmailAddressCode -> Bool
(CheckRecoveryEmailAddressCode
 -> CheckRecoveryEmailAddressCode -> Bool)
-> (CheckRecoveryEmailAddressCode
    -> CheckRecoveryEmailAddressCode -> Bool)
-> Eq CheckRecoveryEmailAddressCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckRecoveryEmailAddressCode
-> CheckRecoveryEmailAddressCode -> Bool
$c/= :: CheckRecoveryEmailAddressCode
-> CheckRecoveryEmailAddressCode -> Bool
== :: CheckRecoveryEmailAddressCode
-> CheckRecoveryEmailAddressCode -> Bool
$c== :: CheckRecoveryEmailAddressCode
-> CheckRecoveryEmailAddressCode -> Bool
Eq, (forall x.
 CheckRecoveryEmailAddressCode
 -> Rep CheckRecoveryEmailAddressCode x)
-> (forall x.
    Rep CheckRecoveryEmailAddressCode x
    -> CheckRecoveryEmailAddressCode)
-> Generic CheckRecoveryEmailAddressCode
forall x.
Rep CheckRecoveryEmailAddressCode x
-> CheckRecoveryEmailAddressCode
forall x.
CheckRecoveryEmailAddressCode
-> Rep CheckRecoveryEmailAddressCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckRecoveryEmailAddressCode x
-> CheckRecoveryEmailAddressCode
$cfrom :: forall x.
CheckRecoveryEmailAddressCode
-> Rep CheckRecoveryEmailAddressCode x
Generic)

-- | Parameter of Function resendRecoveryEmailAddressCode
data ResendRecoveryEmailAddressCode
  = -- | Resends the 2-step verification recovery email address verification code
    ResendRecoveryEmailAddressCode
      {
      }
  deriving (Int -> ResendRecoveryEmailAddressCode -> ShowS
[ResendRecoveryEmailAddressCode] -> ShowS
ResendRecoveryEmailAddressCode -> String
(Int -> ResendRecoveryEmailAddressCode -> ShowS)
-> (ResendRecoveryEmailAddressCode -> String)
-> ([ResendRecoveryEmailAddressCode] -> ShowS)
-> Show ResendRecoveryEmailAddressCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendRecoveryEmailAddressCode] -> ShowS
$cshowList :: [ResendRecoveryEmailAddressCode] -> ShowS
show :: ResendRecoveryEmailAddressCode -> String
$cshow :: ResendRecoveryEmailAddressCode -> String
showsPrec :: Int -> ResendRecoveryEmailAddressCode -> ShowS
$cshowsPrec :: Int -> ResendRecoveryEmailAddressCode -> ShowS
Show, ResendRecoveryEmailAddressCode
-> ResendRecoveryEmailAddressCode -> Bool
(ResendRecoveryEmailAddressCode
 -> ResendRecoveryEmailAddressCode -> Bool)
-> (ResendRecoveryEmailAddressCode
    -> ResendRecoveryEmailAddressCode -> Bool)
-> Eq ResendRecoveryEmailAddressCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendRecoveryEmailAddressCode
-> ResendRecoveryEmailAddressCode -> Bool
$c/= :: ResendRecoveryEmailAddressCode
-> ResendRecoveryEmailAddressCode -> Bool
== :: ResendRecoveryEmailAddressCode
-> ResendRecoveryEmailAddressCode -> Bool
$c== :: ResendRecoveryEmailAddressCode
-> ResendRecoveryEmailAddressCode -> Bool
Eq, (forall x.
 ResendRecoveryEmailAddressCode
 -> Rep ResendRecoveryEmailAddressCode x)
-> (forall x.
    Rep ResendRecoveryEmailAddressCode x
    -> ResendRecoveryEmailAddressCode)
-> Generic ResendRecoveryEmailAddressCode
forall x.
Rep ResendRecoveryEmailAddressCode x
-> ResendRecoveryEmailAddressCode
forall x.
ResendRecoveryEmailAddressCode
-> Rep ResendRecoveryEmailAddressCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendRecoveryEmailAddressCode x
-> ResendRecoveryEmailAddressCode
$cfrom :: forall x.
ResendRecoveryEmailAddressCode
-> Rep ResendRecoveryEmailAddressCode x
Generic)

-- | Parameter of Function requestPasswordRecovery
data RequestPasswordRecovery
  = -- | Requests to send a password recovery code to an email address that was previously set up
    RequestPasswordRecovery
      {
      }
  deriving (Int -> RequestPasswordRecovery -> ShowS
[RequestPasswordRecovery] -> ShowS
RequestPasswordRecovery -> String
(Int -> RequestPasswordRecovery -> ShowS)
-> (RequestPasswordRecovery -> String)
-> ([RequestPasswordRecovery] -> ShowS)
-> Show RequestPasswordRecovery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RequestPasswordRecovery] -> ShowS
$cshowList :: [RequestPasswordRecovery] -> ShowS
show :: RequestPasswordRecovery -> String
$cshow :: RequestPasswordRecovery -> String
showsPrec :: Int -> RequestPasswordRecovery -> ShowS
$cshowsPrec :: Int -> RequestPasswordRecovery -> ShowS
Show, RequestPasswordRecovery -> RequestPasswordRecovery -> Bool
(RequestPasswordRecovery -> RequestPasswordRecovery -> Bool)
-> (RequestPasswordRecovery -> RequestPasswordRecovery -> Bool)
-> Eq RequestPasswordRecovery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RequestPasswordRecovery -> RequestPasswordRecovery -> Bool
$c/= :: RequestPasswordRecovery -> RequestPasswordRecovery -> Bool
== :: RequestPasswordRecovery -> RequestPasswordRecovery -> Bool
$c== :: RequestPasswordRecovery -> RequestPasswordRecovery -> Bool
Eq, (forall x.
 RequestPasswordRecovery -> Rep RequestPasswordRecovery x)
-> (forall x.
    Rep RequestPasswordRecovery x -> RequestPasswordRecovery)
-> Generic RequestPasswordRecovery
forall x. Rep RequestPasswordRecovery x -> RequestPasswordRecovery
forall x. RequestPasswordRecovery -> Rep RequestPasswordRecovery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RequestPasswordRecovery x -> RequestPasswordRecovery
$cfrom :: forall x. RequestPasswordRecovery -> Rep RequestPasswordRecovery x
Generic)

-- | Parameter of Function recoverPassword
data RecoverPassword
  = -- | Recovers the password using a recovery code sent to an email address that was previously set up
    RecoverPassword
      { -- | Recovery code to check
        RecoverPassword -> T
recovery_code :: T
      }
  deriving (Int -> RecoverPassword -> ShowS
[RecoverPassword] -> ShowS
RecoverPassword -> String
(Int -> RecoverPassword -> ShowS)
-> (RecoverPassword -> String)
-> ([RecoverPassword] -> ShowS)
-> Show RecoverPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RecoverPassword] -> ShowS
$cshowList :: [RecoverPassword] -> ShowS
show :: RecoverPassword -> String
$cshow :: RecoverPassword -> String
showsPrec :: Int -> RecoverPassword -> ShowS
$cshowsPrec :: Int -> RecoverPassword -> ShowS
Show, RecoverPassword -> RecoverPassword -> Bool
(RecoverPassword -> RecoverPassword -> Bool)
-> (RecoverPassword -> RecoverPassword -> Bool)
-> Eq RecoverPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RecoverPassword -> RecoverPassword -> Bool
$c/= :: RecoverPassword -> RecoverPassword -> Bool
== :: RecoverPassword -> RecoverPassword -> Bool
$c== :: RecoverPassword -> RecoverPassword -> Bool
Eq, (forall x. RecoverPassword -> Rep RecoverPassword x)
-> (forall x. Rep RecoverPassword x -> RecoverPassword)
-> Generic RecoverPassword
forall x. Rep RecoverPassword x -> RecoverPassword
forall x. RecoverPassword -> Rep RecoverPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RecoverPassword x -> RecoverPassword
$cfrom :: forall x. RecoverPassword -> Rep RecoverPassword x
Generic)

-- | Parameter of Function createTemporaryPassword
data CreateTemporaryPassword
  = -- | Creates a new temporary password for processing payments
    CreateTemporaryPassword
      { -- | Persistent user password
        CreateTemporaryPassword -> T
password :: T,
        -- | Time during which the temporary password will be valid, in seconds; should be between 60 and 86400
        CreateTemporaryPassword -> Int
valid_for :: I32
      }
  deriving (Int -> CreateTemporaryPassword -> ShowS
[CreateTemporaryPassword] -> ShowS
CreateTemporaryPassword -> String
(Int -> CreateTemporaryPassword -> ShowS)
-> (CreateTemporaryPassword -> String)
-> ([CreateTemporaryPassword] -> ShowS)
-> Show CreateTemporaryPassword
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTemporaryPassword] -> ShowS
$cshowList :: [CreateTemporaryPassword] -> ShowS
show :: CreateTemporaryPassword -> String
$cshow :: CreateTemporaryPassword -> String
showsPrec :: Int -> CreateTemporaryPassword -> ShowS
$cshowsPrec :: Int -> CreateTemporaryPassword -> ShowS
Show, CreateTemporaryPassword -> CreateTemporaryPassword -> Bool
(CreateTemporaryPassword -> CreateTemporaryPassword -> Bool)
-> (CreateTemporaryPassword -> CreateTemporaryPassword -> Bool)
-> Eq CreateTemporaryPassword
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTemporaryPassword -> CreateTemporaryPassword -> Bool
$c/= :: CreateTemporaryPassword -> CreateTemporaryPassword -> Bool
== :: CreateTemporaryPassword -> CreateTemporaryPassword -> Bool
$c== :: CreateTemporaryPassword -> CreateTemporaryPassword -> Bool
Eq, (forall x.
 CreateTemporaryPassword -> Rep CreateTemporaryPassword x)
-> (forall x.
    Rep CreateTemporaryPassword x -> CreateTemporaryPassword)
-> Generic CreateTemporaryPassword
forall x. Rep CreateTemporaryPassword x -> CreateTemporaryPassword
forall x. CreateTemporaryPassword -> Rep CreateTemporaryPassword x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateTemporaryPassword x -> CreateTemporaryPassword
$cfrom :: forall x. CreateTemporaryPassword -> Rep CreateTemporaryPassword x
Generic)

-- | Parameter of Function getTemporaryPasswordState
data GetTemporaryPasswordState
  = -- | Returns information about the current temporary password
    GetTemporaryPasswordState
      {
      }
  deriving (Int -> GetTemporaryPasswordState -> ShowS
[GetTemporaryPasswordState] -> ShowS
GetTemporaryPasswordState -> String
(Int -> GetTemporaryPasswordState -> ShowS)
-> (GetTemporaryPasswordState -> String)
-> ([GetTemporaryPasswordState] -> ShowS)
-> Show GetTemporaryPasswordState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTemporaryPasswordState] -> ShowS
$cshowList :: [GetTemporaryPasswordState] -> ShowS
show :: GetTemporaryPasswordState -> String
$cshow :: GetTemporaryPasswordState -> String
showsPrec :: Int -> GetTemporaryPasswordState -> ShowS
$cshowsPrec :: Int -> GetTemporaryPasswordState -> ShowS
Show, GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool
(GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool)
-> (GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool)
-> Eq GetTemporaryPasswordState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool
$c/= :: GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool
== :: GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool
$c== :: GetTemporaryPasswordState -> GetTemporaryPasswordState -> Bool
Eq, (forall x.
 GetTemporaryPasswordState -> Rep GetTemporaryPasswordState x)
-> (forall x.
    Rep GetTemporaryPasswordState x -> GetTemporaryPasswordState)
-> Generic GetTemporaryPasswordState
forall x.
Rep GetTemporaryPasswordState x -> GetTemporaryPasswordState
forall x.
GetTemporaryPasswordState -> Rep GetTemporaryPasswordState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetTemporaryPasswordState x -> GetTemporaryPasswordState
$cfrom :: forall x.
GetTemporaryPasswordState -> Rep GetTemporaryPasswordState x
Generic)

-- | Parameter of Function getMe
data GetMe
  = -- | Returns the current user
    GetMe
      {
      }
  deriving (Int -> GetMe -> ShowS
[GetMe] -> ShowS
GetMe -> String
(Int -> GetMe -> ShowS)
-> (GetMe -> String) -> ([GetMe] -> ShowS) -> Show GetMe
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMe] -> ShowS
$cshowList :: [GetMe] -> ShowS
show :: GetMe -> String
$cshow :: GetMe -> String
showsPrec :: Int -> GetMe -> ShowS
$cshowsPrec :: Int -> GetMe -> ShowS
Show, GetMe -> GetMe -> Bool
(GetMe -> GetMe -> Bool) -> (GetMe -> GetMe -> Bool) -> Eq GetMe
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMe -> GetMe -> Bool
$c/= :: GetMe -> GetMe -> Bool
== :: GetMe -> GetMe -> Bool
$c== :: GetMe -> GetMe -> Bool
Eq, (forall x. GetMe -> Rep GetMe x)
-> (forall x. Rep GetMe x -> GetMe) -> Generic GetMe
forall x. Rep GetMe x -> GetMe
forall x. GetMe -> Rep GetMe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMe x -> GetMe
$cfrom :: forall x. GetMe -> Rep GetMe x
Generic)

-- | Parameter of Function getUser
data GetUser
  = -- | Returns information about a user by their identifier. This is an offline request if the current user is not a bot
    GetUser
      { -- | User identifier
        GetUser -> Int
user_id :: I32
      }
  deriving (Int -> GetUser -> ShowS
[GetUser] -> ShowS
GetUser -> String
(Int -> GetUser -> ShowS)
-> (GetUser -> String) -> ([GetUser] -> ShowS) -> Show GetUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUser] -> ShowS
$cshowList :: [GetUser] -> ShowS
show :: GetUser -> String
$cshow :: GetUser -> String
showsPrec :: Int -> GetUser -> ShowS
$cshowsPrec :: Int -> GetUser -> ShowS
Show, GetUser -> GetUser -> Bool
(GetUser -> GetUser -> Bool)
-> (GetUser -> GetUser -> Bool) -> Eq GetUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUser -> GetUser -> Bool
$c/= :: GetUser -> GetUser -> Bool
== :: GetUser -> GetUser -> Bool
$c== :: GetUser -> GetUser -> Bool
Eq, (forall x. GetUser -> Rep GetUser x)
-> (forall x. Rep GetUser x -> GetUser) -> Generic GetUser
forall x. Rep GetUser x -> GetUser
forall x. GetUser -> Rep GetUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUser x -> GetUser
$cfrom :: forall x. GetUser -> Rep GetUser x
Generic)

-- | Parameter of Function getUserFullInfo
data GetUserFullInfo
  = -- | Returns full information about a user by their identifier
    GetUserFullInfo
      { -- | User identifier
        GetUserFullInfo -> Int
user_id :: I32
      }
  deriving (Int -> GetUserFullInfo -> ShowS
[GetUserFullInfo] -> ShowS
GetUserFullInfo -> String
(Int -> GetUserFullInfo -> ShowS)
-> (GetUserFullInfo -> String)
-> ([GetUserFullInfo] -> ShowS)
-> Show GetUserFullInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUserFullInfo] -> ShowS
$cshowList :: [GetUserFullInfo] -> ShowS
show :: GetUserFullInfo -> String
$cshow :: GetUserFullInfo -> String
showsPrec :: Int -> GetUserFullInfo -> ShowS
$cshowsPrec :: Int -> GetUserFullInfo -> ShowS
Show, GetUserFullInfo -> GetUserFullInfo -> Bool
(GetUserFullInfo -> GetUserFullInfo -> Bool)
-> (GetUserFullInfo -> GetUserFullInfo -> Bool)
-> Eq GetUserFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUserFullInfo -> GetUserFullInfo -> Bool
$c/= :: GetUserFullInfo -> GetUserFullInfo -> Bool
== :: GetUserFullInfo -> GetUserFullInfo -> Bool
$c== :: GetUserFullInfo -> GetUserFullInfo -> Bool
Eq, (forall x. GetUserFullInfo -> Rep GetUserFullInfo x)
-> (forall x. Rep GetUserFullInfo x -> GetUserFullInfo)
-> Generic GetUserFullInfo
forall x. Rep GetUserFullInfo x -> GetUserFullInfo
forall x. GetUserFullInfo -> Rep GetUserFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUserFullInfo x -> GetUserFullInfo
$cfrom :: forall x. GetUserFullInfo -> Rep GetUserFullInfo x
Generic)

-- | Parameter of Function getBasicGroup
data GetBasicGroup
  = -- | Returns information about a basic group by its identifier. This is an offline request if the current user is not a bot
    GetBasicGroup
      { -- | Basic group identifier
        GetBasicGroup -> Int
basic_group_id :: I32
      }
  deriving (Int -> GetBasicGroup -> ShowS
[GetBasicGroup] -> ShowS
GetBasicGroup -> String
(Int -> GetBasicGroup -> ShowS)
-> (GetBasicGroup -> String)
-> ([GetBasicGroup] -> ShowS)
-> Show GetBasicGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBasicGroup] -> ShowS
$cshowList :: [GetBasicGroup] -> ShowS
show :: GetBasicGroup -> String
$cshow :: GetBasicGroup -> String
showsPrec :: Int -> GetBasicGroup -> ShowS
$cshowsPrec :: Int -> GetBasicGroup -> ShowS
Show, GetBasicGroup -> GetBasicGroup -> Bool
(GetBasicGroup -> GetBasicGroup -> Bool)
-> (GetBasicGroup -> GetBasicGroup -> Bool) -> Eq GetBasicGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBasicGroup -> GetBasicGroup -> Bool
$c/= :: GetBasicGroup -> GetBasicGroup -> Bool
== :: GetBasicGroup -> GetBasicGroup -> Bool
$c== :: GetBasicGroup -> GetBasicGroup -> Bool
Eq, (forall x. GetBasicGroup -> Rep GetBasicGroup x)
-> (forall x. Rep GetBasicGroup x -> GetBasicGroup)
-> Generic GetBasicGroup
forall x. Rep GetBasicGroup x -> GetBasicGroup
forall x. GetBasicGroup -> Rep GetBasicGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBasicGroup x -> GetBasicGroup
$cfrom :: forall x. GetBasicGroup -> Rep GetBasicGroup x
Generic)

-- | Parameter of Function getBasicGroupFullInfo
data GetBasicGroupFullInfo
  = -- | Returns full information about a basic group by its identifier
    GetBasicGroupFullInfo
      { -- | Basic group identifier
        GetBasicGroupFullInfo -> Int
basic_group_id :: I32
      }
  deriving (Int -> GetBasicGroupFullInfo -> ShowS
[GetBasicGroupFullInfo] -> ShowS
GetBasicGroupFullInfo -> String
(Int -> GetBasicGroupFullInfo -> ShowS)
-> (GetBasicGroupFullInfo -> String)
-> ([GetBasicGroupFullInfo] -> ShowS)
-> Show GetBasicGroupFullInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBasicGroupFullInfo] -> ShowS
$cshowList :: [GetBasicGroupFullInfo] -> ShowS
show :: GetBasicGroupFullInfo -> String
$cshow :: GetBasicGroupFullInfo -> String
showsPrec :: Int -> GetBasicGroupFullInfo -> ShowS
$cshowsPrec :: Int -> GetBasicGroupFullInfo -> ShowS
Show, GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool
(GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool)
-> (GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool)
-> Eq GetBasicGroupFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool
$c/= :: GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool
== :: GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool
$c== :: GetBasicGroupFullInfo -> GetBasicGroupFullInfo -> Bool
Eq, (forall x. GetBasicGroupFullInfo -> Rep GetBasicGroupFullInfo x)
-> (forall x. Rep GetBasicGroupFullInfo x -> GetBasicGroupFullInfo)
-> Generic GetBasicGroupFullInfo
forall x. Rep GetBasicGroupFullInfo x -> GetBasicGroupFullInfo
forall x. GetBasicGroupFullInfo -> Rep GetBasicGroupFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBasicGroupFullInfo x -> GetBasicGroupFullInfo
$cfrom :: forall x. GetBasicGroupFullInfo -> Rep GetBasicGroupFullInfo x
Generic)

-- | Parameter of Function getSupergroup
data GetSupergroup
  = -- | Returns information about a supergroup or a channel by its identifier. This is an offline request if the current user is not a bot
    GetSupergroup
      { -- | Supergroup or channel identifier
        GetSupergroup -> Int
supergroup_id :: I32
      }
  deriving (Int -> GetSupergroup -> ShowS
[GetSupergroup] -> ShowS
GetSupergroup -> String
(Int -> GetSupergroup -> ShowS)
-> (GetSupergroup -> String)
-> ([GetSupergroup] -> ShowS)
-> Show GetSupergroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSupergroup] -> ShowS
$cshowList :: [GetSupergroup] -> ShowS
show :: GetSupergroup -> String
$cshow :: GetSupergroup -> String
showsPrec :: Int -> GetSupergroup -> ShowS
$cshowsPrec :: Int -> GetSupergroup -> ShowS
Show, GetSupergroup -> GetSupergroup -> Bool
(GetSupergroup -> GetSupergroup -> Bool)
-> (GetSupergroup -> GetSupergroup -> Bool) -> Eq GetSupergroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSupergroup -> GetSupergroup -> Bool
$c/= :: GetSupergroup -> GetSupergroup -> Bool
== :: GetSupergroup -> GetSupergroup -> Bool
$c== :: GetSupergroup -> GetSupergroup -> Bool
Eq, (forall x. GetSupergroup -> Rep GetSupergroup x)
-> (forall x. Rep GetSupergroup x -> GetSupergroup)
-> Generic GetSupergroup
forall x. Rep GetSupergroup x -> GetSupergroup
forall x. GetSupergroup -> Rep GetSupergroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSupergroup x -> GetSupergroup
$cfrom :: forall x. GetSupergroup -> Rep GetSupergroup x
Generic)

-- | Parameter of Function getSupergroupFullInfo
data GetSupergroupFullInfo
  = -- | Returns full information about a supergroup or a channel by its identifier, cached for up to 1 minute
    GetSupergroupFullInfo
      { -- | Supergroup or channel identifier
        GetSupergroupFullInfo -> Int
supergroup_id :: I32
      }
  deriving (Int -> GetSupergroupFullInfo -> ShowS
[GetSupergroupFullInfo] -> ShowS
GetSupergroupFullInfo -> String
(Int -> GetSupergroupFullInfo -> ShowS)
-> (GetSupergroupFullInfo -> String)
-> ([GetSupergroupFullInfo] -> ShowS)
-> Show GetSupergroupFullInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSupergroupFullInfo] -> ShowS
$cshowList :: [GetSupergroupFullInfo] -> ShowS
show :: GetSupergroupFullInfo -> String
$cshow :: GetSupergroupFullInfo -> String
showsPrec :: Int -> GetSupergroupFullInfo -> ShowS
$cshowsPrec :: Int -> GetSupergroupFullInfo -> ShowS
Show, GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool
(GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool)
-> (GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool)
-> Eq GetSupergroupFullInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool
$c/= :: GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool
== :: GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool
$c== :: GetSupergroupFullInfo -> GetSupergroupFullInfo -> Bool
Eq, (forall x. GetSupergroupFullInfo -> Rep GetSupergroupFullInfo x)
-> (forall x. Rep GetSupergroupFullInfo x -> GetSupergroupFullInfo)
-> Generic GetSupergroupFullInfo
forall x. Rep GetSupergroupFullInfo x -> GetSupergroupFullInfo
forall x. GetSupergroupFullInfo -> Rep GetSupergroupFullInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSupergroupFullInfo x -> GetSupergroupFullInfo
$cfrom :: forall x. GetSupergroupFullInfo -> Rep GetSupergroupFullInfo x
Generic)

-- | Parameter of Function getSecretChat
data GetSecretChat
  = -- | Returns information about a secret chat by its identifier. This is an offline request
    GetSecretChat
      { -- | Secret chat identifier
        GetSecretChat -> Int
secret_chat_id :: I32
      }
  deriving (Int -> GetSecretChat -> ShowS
[GetSecretChat] -> ShowS
GetSecretChat -> String
(Int -> GetSecretChat -> ShowS)
-> (GetSecretChat -> String)
-> ([GetSecretChat] -> ShowS)
-> Show GetSecretChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSecretChat] -> ShowS
$cshowList :: [GetSecretChat] -> ShowS
show :: GetSecretChat -> String
$cshow :: GetSecretChat -> String
showsPrec :: Int -> GetSecretChat -> ShowS
$cshowsPrec :: Int -> GetSecretChat -> ShowS
Show, GetSecretChat -> GetSecretChat -> Bool
(GetSecretChat -> GetSecretChat -> Bool)
-> (GetSecretChat -> GetSecretChat -> Bool) -> Eq GetSecretChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSecretChat -> GetSecretChat -> Bool
$c/= :: GetSecretChat -> GetSecretChat -> Bool
== :: GetSecretChat -> GetSecretChat -> Bool
$c== :: GetSecretChat -> GetSecretChat -> Bool
Eq, (forall x. GetSecretChat -> Rep GetSecretChat x)
-> (forall x. Rep GetSecretChat x -> GetSecretChat)
-> Generic GetSecretChat
forall x. Rep GetSecretChat x -> GetSecretChat
forall x. GetSecretChat -> Rep GetSecretChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSecretChat x -> GetSecretChat
$cfrom :: forall x. GetSecretChat -> Rep GetSecretChat x
Generic)

-- | Parameter of Function getChat
data GetChat
  = -- | Returns information about a chat by its identifier, this is an offline request if the current user is not a bot
    GetChat
      { -- | Chat identifier
        GetChat -> Int
chat_id :: I53
      }
  deriving (Int -> GetChat -> ShowS
[GetChat] -> ShowS
GetChat -> String
(Int -> GetChat -> ShowS)
-> (GetChat -> String) -> ([GetChat] -> ShowS) -> Show GetChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChat] -> ShowS
$cshowList :: [GetChat] -> ShowS
show :: GetChat -> String
$cshow :: GetChat -> String
showsPrec :: Int -> GetChat -> ShowS
$cshowsPrec :: Int -> GetChat -> ShowS
Show, GetChat -> GetChat -> Bool
(GetChat -> GetChat -> Bool)
-> (GetChat -> GetChat -> Bool) -> Eq GetChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChat -> GetChat -> Bool
$c/= :: GetChat -> GetChat -> Bool
== :: GetChat -> GetChat -> Bool
$c== :: GetChat -> GetChat -> Bool
Eq, (forall x. GetChat -> Rep GetChat x)
-> (forall x. Rep GetChat x -> GetChat) -> Generic GetChat
forall x. Rep GetChat x -> GetChat
forall x. GetChat -> Rep GetChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChat x -> GetChat
$cfrom :: forall x. GetChat -> Rep GetChat x
Generic)

-- | Parameter of Function getMessage
data GetMessage
  = -- | Returns information about a message
    GetMessage
      { -- | Identifier of the chat the message belongs to
        GetMessage -> Int
chat_id :: I53,
        -- | Identifier of the message to get
        GetMessage -> Int
message_id :: I53
      }
  deriving (Int -> GetMessage -> ShowS
[GetMessage] -> ShowS
GetMessage -> String
(Int -> GetMessage -> ShowS)
-> (GetMessage -> String)
-> ([GetMessage] -> ShowS)
-> Show GetMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMessage] -> ShowS
$cshowList :: [GetMessage] -> ShowS
show :: GetMessage -> String
$cshow :: GetMessage -> String
showsPrec :: Int -> GetMessage -> ShowS
$cshowsPrec :: Int -> GetMessage -> ShowS
Show, GetMessage -> GetMessage -> Bool
(GetMessage -> GetMessage -> Bool)
-> (GetMessage -> GetMessage -> Bool) -> Eq GetMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMessage -> GetMessage -> Bool
$c/= :: GetMessage -> GetMessage -> Bool
== :: GetMessage -> GetMessage -> Bool
$c== :: GetMessage -> GetMessage -> Bool
Eq, (forall x. GetMessage -> Rep GetMessage x)
-> (forall x. Rep GetMessage x -> GetMessage) -> Generic GetMessage
forall x. Rep GetMessage x -> GetMessage
forall x. GetMessage -> Rep GetMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMessage x -> GetMessage
$cfrom :: forall x. GetMessage -> Rep GetMessage x
Generic)

-- | Parameter of Function getMessageLocally
data GetMessageLocally
  = -- | Returns information about a message, if it is available locally without sending network request. This is an offline request
    GetMessageLocally
      { -- | Identifier of the chat the message belongs to
        GetMessageLocally -> Int
chat_id :: I53,
        -- | Identifier of the message to get
        GetMessageLocally -> Int
message_id :: I53
      }
  deriving (Int -> GetMessageLocally -> ShowS
[GetMessageLocally] -> ShowS
GetMessageLocally -> String
(Int -> GetMessageLocally -> ShowS)
-> (GetMessageLocally -> String)
-> ([GetMessageLocally] -> ShowS)
-> Show GetMessageLocally
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMessageLocally] -> ShowS
$cshowList :: [GetMessageLocally] -> ShowS
show :: GetMessageLocally -> String
$cshow :: GetMessageLocally -> String
showsPrec :: Int -> GetMessageLocally -> ShowS
$cshowsPrec :: Int -> GetMessageLocally -> ShowS
Show, GetMessageLocally -> GetMessageLocally -> Bool
(GetMessageLocally -> GetMessageLocally -> Bool)
-> (GetMessageLocally -> GetMessageLocally -> Bool)
-> Eq GetMessageLocally
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMessageLocally -> GetMessageLocally -> Bool
$c/= :: GetMessageLocally -> GetMessageLocally -> Bool
== :: GetMessageLocally -> GetMessageLocally -> Bool
$c== :: GetMessageLocally -> GetMessageLocally -> Bool
Eq, (forall x. GetMessageLocally -> Rep GetMessageLocally x)
-> (forall x. Rep GetMessageLocally x -> GetMessageLocally)
-> Generic GetMessageLocally
forall x. Rep GetMessageLocally x -> GetMessageLocally
forall x. GetMessageLocally -> Rep GetMessageLocally x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMessageLocally x -> GetMessageLocally
$cfrom :: forall x. GetMessageLocally -> Rep GetMessageLocally x
Generic)

-- | Parameter of Function getRepliedMessage
data GetRepliedMessage
  = -- | Returns information about a message that is replied by given message
    GetRepliedMessage
      { -- | Identifier of the chat the message belongs to
        GetRepliedMessage -> Int
chat_id :: I53,
        -- | Identifier of the message reply to which get
        GetRepliedMessage -> Int
message_id :: I53
      }
  deriving (Int -> GetRepliedMessage -> ShowS
[GetRepliedMessage] -> ShowS
GetRepliedMessage -> String
(Int -> GetRepliedMessage -> ShowS)
-> (GetRepliedMessage -> String)
-> ([GetRepliedMessage] -> ShowS)
-> Show GetRepliedMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRepliedMessage] -> ShowS
$cshowList :: [GetRepliedMessage] -> ShowS
show :: GetRepliedMessage -> String
$cshow :: GetRepliedMessage -> String
showsPrec :: Int -> GetRepliedMessage -> ShowS
$cshowsPrec :: Int -> GetRepliedMessage -> ShowS
Show, GetRepliedMessage -> GetRepliedMessage -> Bool
(GetRepliedMessage -> GetRepliedMessage -> Bool)
-> (GetRepliedMessage -> GetRepliedMessage -> Bool)
-> Eq GetRepliedMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRepliedMessage -> GetRepliedMessage -> Bool
$c/= :: GetRepliedMessage -> GetRepliedMessage -> Bool
== :: GetRepliedMessage -> GetRepliedMessage -> Bool
$c== :: GetRepliedMessage -> GetRepliedMessage -> Bool
Eq, (forall x. GetRepliedMessage -> Rep GetRepliedMessage x)
-> (forall x. Rep GetRepliedMessage x -> GetRepliedMessage)
-> Generic GetRepliedMessage
forall x. Rep GetRepliedMessage x -> GetRepliedMessage
forall x. GetRepliedMessage -> Rep GetRepliedMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRepliedMessage x -> GetRepliedMessage
$cfrom :: forall x. GetRepliedMessage -> Rep GetRepliedMessage x
Generic)

-- | Parameter of Function getChatPinnedMessage
data GetChatPinnedMessage
  = -- | Returns information about a pinned chat message
    GetChatPinnedMessage
      { -- | Identifier of the chat the message belongs to
        GetChatPinnedMessage -> Int
chat_id :: I53
      }
  deriving (Int -> GetChatPinnedMessage -> ShowS
[GetChatPinnedMessage] -> ShowS
GetChatPinnedMessage -> String
(Int -> GetChatPinnedMessage -> ShowS)
-> (GetChatPinnedMessage -> String)
-> ([GetChatPinnedMessage] -> ShowS)
-> Show GetChatPinnedMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatPinnedMessage] -> ShowS
$cshowList :: [GetChatPinnedMessage] -> ShowS
show :: GetChatPinnedMessage -> String
$cshow :: GetChatPinnedMessage -> String
showsPrec :: Int -> GetChatPinnedMessage -> ShowS
$cshowsPrec :: Int -> GetChatPinnedMessage -> ShowS
Show, GetChatPinnedMessage -> GetChatPinnedMessage -> Bool
(GetChatPinnedMessage -> GetChatPinnedMessage -> Bool)
-> (GetChatPinnedMessage -> GetChatPinnedMessage -> Bool)
-> Eq GetChatPinnedMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatPinnedMessage -> GetChatPinnedMessage -> Bool
$c/= :: GetChatPinnedMessage -> GetChatPinnedMessage -> Bool
== :: GetChatPinnedMessage -> GetChatPinnedMessage -> Bool
$c== :: GetChatPinnedMessage -> GetChatPinnedMessage -> Bool
Eq, (forall x. GetChatPinnedMessage -> Rep GetChatPinnedMessage x)
-> (forall x. Rep GetChatPinnedMessage x -> GetChatPinnedMessage)
-> Generic GetChatPinnedMessage
forall x. Rep GetChatPinnedMessage x -> GetChatPinnedMessage
forall x. GetChatPinnedMessage -> Rep GetChatPinnedMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatPinnedMessage x -> GetChatPinnedMessage
$cfrom :: forall x. GetChatPinnedMessage -> Rep GetChatPinnedMessage x
Generic)

-- | Parameter of Function getMessages
data GetMessages
  = -- | Returns information about messages. If a message is not found, returns null on the corresponding position of the result
    GetMessages
      { -- | Identifier of the chat the messages belong to
        GetMessages -> Int
chat_id :: I53,
        -- | Identifiers of the messages to get
        GetMessages -> [Int]
message_ids :: ([]) (I53)
      }
  deriving (Int -> GetMessages -> ShowS
[GetMessages] -> ShowS
GetMessages -> String
(Int -> GetMessages -> ShowS)
-> (GetMessages -> String)
-> ([GetMessages] -> ShowS)
-> Show GetMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMessages] -> ShowS
$cshowList :: [GetMessages] -> ShowS
show :: GetMessages -> String
$cshow :: GetMessages -> String
showsPrec :: Int -> GetMessages -> ShowS
$cshowsPrec :: Int -> GetMessages -> ShowS
Show, GetMessages -> GetMessages -> Bool
(GetMessages -> GetMessages -> Bool)
-> (GetMessages -> GetMessages -> Bool) -> Eq GetMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMessages -> GetMessages -> Bool
$c/= :: GetMessages -> GetMessages -> Bool
== :: GetMessages -> GetMessages -> Bool
$c== :: GetMessages -> GetMessages -> Bool
Eq, (forall x. GetMessages -> Rep GetMessages x)
-> (forall x. Rep GetMessages x -> GetMessages)
-> Generic GetMessages
forall x. Rep GetMessages x -> GetMessages
forall x. GetMessages -> Rep GetMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMessages x -> GetMessages
$cfrom :: forall x. GetMessages -> Rep GetMessages x
Generic)

-- | Parameter of Function getFile
data GetFile
  = -- | Returns information about a file; this is an offline request
    GetFile
      { -- | Identifier of the file to get
        GetFile -> Int
file_id :: I32
      }
  deriving (Int -> GetFile -> ShowS
[GetFile] -> ShowS
GetFile -> String
(Int -> GetFile -> ShowS)
-> (GetFile -> String) -> ([GetFile] -> ShowS) -> Show GetFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFile] -> ShowS
$cshowList :: [GetFile] -> ShowS
show :: GetFile -> String
$cshow :: GetFile -> String
showsPrec :: Int -> GetFile -> ShowS
$cshowsPrec :: Int -> GetFile -> ShowS
Show, GetFile -> GetFile -> Bool
(GetFile -> GetFile -> Bool)
-> (GetFile -> GetFile -> Bool) -> Eq GetFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFile -> GetFile -> Bool
$c/= :: GetFile -> GetFile -> Bool
== :: GetFile -> GetFile -> Bool
$c== :: GetFile -> GetFile -> Bool
Eq, (forall x. GetFile -> Rep GetFile x)
-> (forall x. Rep GetFile x -> GetFile) -> Generic GetFile
forall x. Rep GetFile x -> GetFile
forall x. GetFile -> Rep GetFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFile x -> GetFile
$cfrom :: forall x. GetFile -> Rep GetFile x
Generic)

-- | Parameter of Function getRemoteFile
data GetRemoteFile
  = -- | Returns information about a file by its remote ID; this is an offline request. Can be used to register a URL as a file for further uploading, or sending as a message. Even the request succeeds, the file can be used only if it is still accessible to the user.
    GetRemoteFile
      { -- | Remote identifier of the file to get
        GetRemoteFile -> T
remote_file_id :: T,
        -- | File type, if known
        GetRemoteFile -> FileType
file_type :: FileType
      }
  deriving (Int -> GetRemoteFile -> ShowS
[GetRemoteFile] -> ShowS
GetRemoteFile -> String
(Int -> GetRemoteFile -> ShowS)
-> (GetRemoteFile -> String)
-> ([GetRemoteFile] -> ShowS)
-> Show GetRemoteFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRemoteFile] -> ShowS
$cshowList :: [GetRemoteFile] -> ShowS
show :: GetRemoteFile -> String
$cshow :: GetRemoteFile -> String
showsPrec :: Int -> GetRemoteFile -> ShowS
$cshowsPrec :: Int -> GetRemoteFile -> ShowS
Show, GetRemoteFile -> GetRemoteFile -> Bool
(GetRemoteFile -> GetRemoteFile -> Bool)
-> (GetRemoteFile -> GetRemoteFile -> Bool) -> Eq GetRemoteFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRemoteFile -> GetRemoteFile -> Bool
$c/= :: GetRemoteFile -> GetRemoteFile -> Bool
== :: GetRemoteFile -> GetRemoteFile -> Bool
$c== :: GetRemoteFile -> GetRemoteFile -> Bool
Eq, (forall x. GetRemoteFile -> Rep GetRemoteFile x)
-> (forall x. Rep GetRemoteFile x -> GetRemoteFile)
-> Generic GetRemoteFile
forall x. Rep GetRemoteFile x -> GetRemoteFile
forall x. GetRemoteFile -> Rep GetRemoteFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRemoteFile x -> GetRemoteFile
$cfrom :: forall x. GetRemoteFile -> Rep GetRemoteFile x
Generic)

-- | Parameter of Function getChats
data GetChats
  = -- | Returns an ordered list of chats in a chat list. Chats are sorted by the pair (order, chat_id) in decreasing order. (For example, to get a list of chats from the beginning, the offset_order should be equal to a biggest signed 64-bit number 9223372036854775807 == 2^63 - 1).
    GetChats
      { -- | The chat list in which to return chats
        GetChats -> ChatList
chat_list :: ChatList,
        -- | Chat order to return chats from
        GetChats -> I64
offset_order :: I64,
        -- | Chat identifier to return chats from
        GetChats -> Int
offset_chat_id :: I53,
        -- | The maximum number of chats to be returned. It is possible that fewer chats than the limit are returned even if the end of the list is not reached
        GetChats -> Int
limit :: I32
      }
  deriving (Int -> GetChats -> ShowS
[GetChats] -> ShowS
GetChats -> String
(Int -> GetChats -> ShowS)
-> (GetChats -> String) -> ([GetChats] -> ShowS) -> Show GetChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChats] -> ShowS
$cshowList :: [GetChats] -> ShowS
show :: GetChats -> String
$cshow :: GetChats -> String
showsPrec :: Int -> GetChats -> ShowS
$cshowsPrec :: Int -> GetChats -> ShowS
Show, GetChats -> GetChats -> Bool
(GetChats -> GetChats -> Bool)
-> (GetChats -> GetChats -> Bool) -> Eq GetChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChats -> GetChats -> Bool
$c/= :: GetChats -> GetChats -> Bool
== :: GetChats -> GetChats -> Bool
$c== :: GetChats -> GetChats -> Bool
Eq, (forall x. GetChats -> Rep GetChats x)
-> (forall x. Rep GetChats x -> GetChats) -> Generic GetChats
forall x. Rep GetChats x -> GetChats
forall x. GetChats -> Rep GetChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChats x -> GetChats
$cfrom :: forall x. GetChats -> Rep GetChats x
Generic)

-- | Parameter of Function searchPublicChat
data SearchPublicChat
  = -- | Searches a public chat by its username. Currently only private chats, supergroups and channels can be public. Returns the chat if found; otherwise an error is returned
    SearchPublicChat
      { -- | Username to be resolved
        SearchPublicChat -> T
username :: T
      }
  deriving (Int -> SearchPublicChat -> ShowS
[SearchPublicChat] -> ShowS
SearchPublicChat -> String
(Int -> SearchPublicChat -> ShowS)
-> (SearchPublicChat -> String)
-> ([SearchPublicChat] -> ShowS)
-> Show SearchPublicChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchPublicChat] -> ShowS
$cshowList :: [SearchPublicChat] -> ShowS
show :: SearchPublicChat -> String
$cshow :: SearchPublicChat -> String
showsPrec :: Int -> SearchPublicChat -> ShowS
$cshowsPrec :: Int -> SearchPublicChat -> ShowS
Show, SearchPublicChat -> SearchPublicChat -> Bool
(SearchPublicChat -> SearchPublicChat -> Bool)
-> (SearchPublicChat -> SearchPublicChat -> Bool)
-> Eq SearchPublicChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchPublicChat -> SearchPublicChat -> Bool
$c/= :: SearchPublicChat -> SearchPublicChat -> Bool
== :: SearchPublicChat -> SearchPublicChat -> Bool
$c== :: SearchPublicChat -> SearchPublicChat -> Bool
Eq, (forall x. SearchPublicChat -> Rep SearchPublicChat x)
-> (forall x. Rep SearchPublicChat x -> SearchPublicChat)
-> Generic SearchPublicChat
forall x. Rep SearchPublicChat x -> SearchPublicChat
forall x. SearchPublicChat -> Rep SearchPublicChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchPublicChat x -> SearchPublicChat
$cfrom :: forall x. SearchPublicChat -> Rep SearchPublicChat x
Generic)

-- | Parameter of Function searchPublicChats
data SearchPublicChats
  = -- | Searches public chats by looking for specified query in their username and title. Currently only private chats, supergroups and channels can be public. Returns a meaningful number of results. Returns nothing if the length of the searched username prefix is less than 5. Excludes private chats with contacts and chats from the chat list from the results
    SearchPublicChats
      { -- | Query to search for
        SearchPublicChats -> T
query :: T
      }
  deriving (Int -> SearchPublicChats -> ShowS
[SearchPublicChats] -> ShowS
SearchPublicChats -> String
(Int -> SearchPublicChats -> ShowS)
-> (SearchPublicChats -> String)
-> ([SearchPublicChats] -> ShowS)
-> Show SearchPublicChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchPublicChats] -> ShowS
$cshowList :: [SearchPublicChats] -> ShowS
show :: SearchPublicChats -> String
$cshow :: SearchPublicChats -> String
showsPrec :: Int -> SearchPublicChats -> ShowS
$cshowsPrec :: Int -> SearchPublicChats -> ShowS
Show, SearchPublicChats -> SearchPublicChats -> Bool
(SearchPublicChats -> SearchPublicChats -> Bool)
-> (SearchPublicChats -> SearchPublicChats -> Bool)
-> Eq SearchPublicChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchPublicChats -> SearchPublicChats -> Bool
$c/= :: SearchPublicChats -> SearchPublicChats -> Bool
== :: SearchPublicChats -> SearchPublicChats -> Bool
$c== :: SearchPublicChats -> SearchPublicChats -> Bool
Eq, (forall x. SearchPublicChats -> Rep SearchPublicChats x)
-> (forall x. Rep SearchPublicChats x -> SearchPublicChats)
-> Generic SearchPublicChats
forall x. Rep SearchPublicChats x -> SearchPublicChats
forall x. SearchPublicChats -> Rep SearchPublicChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchPublicChats x -> SearchPublicChats
$cfrom :: forall x. SearchPublicChats -> Rep SearchPublicChats x
Generic)

-- | Parameter of Function searchChats
data SearchChats
  = -- | Searches for the specified query in the title and username of already known chats, this is an offline request. Returns chats in the order seen in the chat list
    SearchChats
      { -- | Query to search for. If the query is empty, returns up to 20 recently found chats
        SearchChats -> T
query :: T,
        -- | The maximum number of chats to be returned
        SearchChats -> Int
limit :: I32
      }
  deriving (Int -> SearchChats -> ShowS
[SearchChats] -> ShowS
SearchChats -> String
(Int -> SearchChats -> ShowS)
-> (SearchChats -> String)
-> ([SearchChats] -> ShowS)
-> Show SearchChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChats] -> ShowS
$cshowList :: [SearchChats] -> ShowS
show :: SearchChats -> String
$cshow :: SearchChats -> String
showsPrec :: Int -> SearchChats -> ShowS
$cshowsPrec :: Int -> SearchChats -> ShowS
Show, SearchChats -> SearchChats -> Bool
(SearchChats -> SearchChats -> Bool)
-> (SearchChats -> SearchChats -> Bool) -> Eq SearchChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChats -> SearchChats -> Bool
$c/= :: SearchChats -> SearchChats -> Bool
== :: SearchChats -> SearchChats -> Bool
$c== :: SearchChats -> SearchChats -> Bool
Eq, (forall x. SearchChats -> Rep SearchChats x)
-> (forall x. Rep SearchChats x -> SearchChats)
-> Generic SearchChats
forall x. Rep SearchChats x -> SearchChats
forall x. SearchChats -> Rep SearchChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchChats x -> SearchChats
$cfrom :: forall x. SearchChats -> Rep SearchChats x
Generic)

-- | Parameter of Function searchChatsOnServer
data SearchChatsOnServer
  = -- | Searches for the specified query in the title and username of already known chats via request to the server. Returns chats in the order seen in the chat list
    SearchChatsOnServer
      { -- | Query to search for
        SearchChatsOnServer -> T
query :: T,
        -- | The maximum number of chats to be returned
        SearchChatsOnServer -> Int
limit :: I32
      }
  deriving (Int -> SearchChatsOnServer -> ShowS
[SearchChatsOnServer] -> ShowS
SearchChatsOnServer -> String
(Int -> SearchChatsOnServer -> ShowS)
-> (SearchChatsOnServer -> String)
-> ([SearchChatsOnServer] -> ShowS)
-> Show SearchChatsOnServer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChatsOnServer] -> ShowS
$cshowList :: [SearchChatsOnServer] -> ShowS
show :: SearchChatsOnServer -> String
$cshow :: SearchChatsOnServer -> String
showsPrec :: Int -> SearchChatsOnServer -> ShowS
$cshowsPrec :: Int -> SearchChatsOnServer -> ShowS
Show, SearchChatsOnServer -> SearchChatsOnServer -> Bool
(SearchChatsOnServer -> SearchChatsOnServer -> Bool)
-> (SearchChatsOnServer -> SearchChatsOnServer -> Bool)
-> Eq SearchChatsOnServer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChatsOnServer -> SearchChatsOnServer -> Bool
$c/= :: SearchChatsOnServer -> SearchChatsOnServer -> Bool
== :: SearchChatsOnServer -> SearchChatsOnServer -> Bool
$c== :: SearchChatsOnServer -> SearchChatsOnServer -> Bool
Eq, (forall x. SearchChatsOnServer -> Rep SearchChatsOnServer x)
-> (forall x. Rep SearchChatsOnServer x -> SearchChatsOnServer)
-> Generic SearchChatsOnServer
forall x. Rep SearchChatsOnServer x -> SearchChatsOnServer
forall x. SearchChatsOnServer -> Rep SearchChatsOnServer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchChatsOnServer x -> SearchChatsOnServer
$cfrom :: forall x. SearchChatsOnServer -> Rep SearchChatsOnServer x
Generic)

-- | Parameter of Function searchChatsNearby
data SearchChatsNearby
  = -- | Returns a list of users and location-based supergroups nearby. The list of users nearby will be updated for 60 seconds after the request by the updates updateUsersNearby. The request should be sent again every 25 seconds with adjusted location to not miss new chats
    SearchChatsNearby
      { -- | Current user location
        SearchChatsNearby -> Location
location :: Location
      }
  deriving (Int -> SearchChatsNearby -> ShowS
[SearchChatsNearby] -> ShowS
SearchChatsNearby -> String
(Int -> SearchChatsNearby -> ShowS)
-> (SearchChatsNearby -> String)
-> ([SearchChatsNearby] -> ShowS)
-> Show SearchChatsNearby
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChatsNearby] -> ShowS
$cshowList :: [SearchChatsNearby] -> ShowS
show :: SearchChatsNearby -> String
$cshow :: SearchChatsNearby -> String
showsPrec :: Int -> SearchChatsNearby -> ShowS
$cshowsPrec :: Int -> SearchChatsNearby -> ShowS
Show, SearchChatsNearby -> SearchChatsNearby -> Bool
(SearchChatsNearby -> SearchChatsNearby -> Bool)
-> (SearchChatsNearby -> SearchChatsNearby -> Bool)
-> Eq SearchChatsNearby
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChatsNearby -> SearchChatsNearby -> Bool
$c/= :: SearchChatsNearby -> SearchChatsNearby -> Bool
== :: SearchChatsNearby -> SearchChatsNearby -> Bool
$c== :: SearchChatsNearby -> SearchChatsNearby -> Bool
Eq, (forall x. SearchChatsNearby -> Rep SearchChatsNearby x)
-> (forall x. Rep SearchChatsNearby x -> SearchChatsNearby)
-> Generic SearchChatsNearby
forall x. Rep SearchChatsNearby x -> SearchChatsNearby
forall x. SearchChatsNearby -> Rep SearchChatsNearby x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchChatsNearby x -> SearchChatsNearby
$cfrom :: forall x. SearchChatsNearby -> Rep SearchChatsNearby x
Generic)

-- | Parameter of Function getTopChats
data GetTopChats
  = -- | Returns a list of frequently used chats. Supported only if the chat info database is enabled
    GetTopChats
      { -- | Category of chats to be returned
        GetTopChats -> TopChatCategory
category :: TopChatCategory,
        -- | The maximum number of chats to be returned; up to 30
        GetTopChats -> Int
limit :: I32
      }
  deriving (Int -> GetTopChats -> ShowS
[GetTopChats] -> ShowS
GetTopChats -> String
(Int -> GetTopChats -> ShowS)
-> (GetTopChats -> String)
-> ([GetTopChats] -> ShowS)
-> Show GetTopChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTopChats] -> ShowS
$cshowList :: [GetTopChats] -> ShowS
show :: GetTopChats -> String
$cshow :: GetTopChats -> String
showsPrec :: Int -> GetTopChats -> ShowS
$cshowsPrec :: Int -> GetTopChats -> ShowS
Show, GetTopChats -> GetTopChats -> Bool
(GetTopChats -> GetTopChats -> Bool)
-> (GetTopChats -> GetTopChats -> Bool) -> Eq GetTopChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTopChats -> GetTopChats -> Bool
$c/= :: GetTopChats -> GetTopChats -> Bool
== :: GetTopChats -> GetTopChats -> Bool
$c== :: GetTopChats -> GetTopChats -> Bool
Eq, (forall x. GetTopChats -> Rep GetTopChats x)
-> (forall x. Rep GetTopChats x -> GetTopChats)
-> Generic GetTopChats
forall x. Rep GetTopChats x -> GetTopChats
forall x. GetTopChats -> Rep GetTopChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTopChats x -> GetTopChats
$cfrom :: forall x. GetTopChats -> Rep GetTopChats x
Generic)

-- | Parameter of Function removeTopChat
data RemoveTopChat
  = -- | Removes a chat from the list of frequently used chats. Supported only if the chat info database is enabled
    RemoveTopChat
      { -- | Category of frequently used chats
        RemoveTopChat -> TopChatCategory
category :: TopChatCategory,
        -- | Chat identifier
        RemoveTopChat -> Int
chat_id :: I53
      }
  deriving (Int -> RemoveTopChat -> ShowS
[RemoveTopChat] -> ShowS
RemoveTopChat -> String
(Int -> RemoveTopChat -> ShowS)
-> (RemoveTopChat -> String)
-> ([RemoveTopChat] -> ShowS)
-> Show RemoveTopChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveTopChat] -> ShowS
$cshowList :: [RemoveTopChat] -> ShowS
show :: RemoveTopChat -> String
$cshow :: RemoveTopChat -> String
showsPrec :: Int -> RemoveTopChat -> ShowS
$cshowsPrec :: Int -> RemoveTopChat -> ShowS
Show, RemoveTopChat -> RemoveTopChat -> Bool
(RemoveTopChat -> RemoveTopChat -> Bool)
-> (RemoveTopChat -> RemoveTopChat -> Bool) -> Eq RemoveTopChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveTopChat -> RemoveTopChat -> Bool
$c/= :: RemoveTopChat -> RemoveTopChat -> Bool
== :: RemoveTopChat -> RemoveTopChat -> Bool
$c== :: RemoveTopChat -> RemoveTopChat -> Bool
Eq, (forall x. RemoveTopChat -> Rep RemoveTopChat x)
-> (forall x. Rep RemoveTopChat x -> RemoveTopChat)
-> Generic RemoveTopChat
forall x. Rep RemoveTopChat x -> RemoveTopChat
forall x. RemoveTopChat -> Rep RemoveTopChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveTopChat x -> RemoveTopChat
$cfrom :: forall x. RemoveTopChat -> Rep RemoveTopChat x
Generic)

-- | Parameter of Function addRecentlyFoundChat
data AddRecentlyFoundChat
  = -- | Adds a chat to the list of recently found chats. The chat is added to the beginning of the list. If the chat is already in the list, it will be removed from the list first
    AddRecentlyFoundChat
      { -- | Identifier of the chat to add
        AddRecentlyFoundChat -> Int
chat_id :: I53
      }
  deriving (Int -> AddRecentlyFoundChat -> ShowS
[AddRecentlyFoundChat] -> ShowS
AddRecentlyFoundChat -> String
(Int -> AddRecentlyFoundChat -> ShowS)
-> (AddRecentlyFoundChat -> String)
-> ([AddRecentlyFoundChat] -> ShowS)
-> Show AddRecentlyFoundChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddRecentlyFoundChat] -> ShowS
$cshowList :: [AddRecentlyFoundChat] -> ShowS
show :: AddRecentlyFoundChat -> String
$cshow :: AddRecentlyFoundChat -> String
showsPrec :: Int -> AddRecentlyFoundChat -> ShowS
$cshowsPrec :: Int -> AddRecentlyFoundChat -> ShowS
Show, AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool
(AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool)
-> (AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool)
-> Eq AddRecentlyFoundChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool
$c/= :: AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool
== :: AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool
$c== :: AddRecentlyFoundChat -> AddRecentlyFoundChat -> Bool
Eq, (forall x. AddRecentlyFoundChat -> Rep AddRecentlyFoundChat x)
-> (forall x. Rep AddRecentlyFoundChat x -> AddRecentlyFoundChat)
-> Generic AddRecentlyFoundChat
forall x. Rep AddRecentlyFoundChat x -> AddRecentlyFoundChat
forall x. AddRecentlyFoundChat -> Rep AddRecentlyFoundChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddRecentlyFoundChat x -> AddRecentlyFoundChat
$cfrom :: forall x. AddRecentlyFoundChat -> Rep AddRecentlyFoundChat x
Generic)

-- | Parameter of Function removeRecentlyFoundChat
data RemoveRecentlyFoundChat
  = -- | Removes a chat from the list of recently found chats
    RemoveRecentlyFoundChat
      { -- | Identifier of the chat to be removed
        RemoveRecentlyFoundChat -> Int
chat_id :: I53
      }
  deriving (Int -> RemoveRecentlyFoundChat -> ShowS
[RemoveRecentlyFoundChat] -> ShowS
RemoveRecentlyFoundChat -> String
(Int -> RemoveRecentlyFoundChat -> ShowS)
-> (RemoveRecentlyFoundChat -> String)
-> ([RemoveRecentlyFoundChat] -> ShowS)
-> Show RemoveRecentlyFoundChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRecentlyFoundChat] -> ShowS
$cshowList :: [RemoveRecentlyFoundChat] -> ShowS
show :: RemoveRecentlyFoundChat -> String
$cshow :: RemoveRecentlyFoundChat -> String
showsPrec :: Int -> RemoveRecentlyFoundChat -> ShowS
$cshowsPrec :: Int -> RemoveRecentlyFoundChat -> ShowS
Show, RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool
(RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool)
-> (RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool)
-> Eq RemoveRecentlyFoundChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool
$c/= :: RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool
== :: RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool
$c== :: RemoveRecentlyFoundChat -> RemoveRecentlyFoundChat -> Bool
Eq, (forall x.
 RemoveRecentlyFoundChat -> Rep RemoveRecentlyFoundChat x)
-> (forall x.
    Rep RemoveRecentlyFoundChat x -> RemoveRecentlyFoundChat)
-> Generic RemoveRecentlyFoundChat
forall x. Rep RemoveRecentlyFoundChat x -> RemoveRecentlyFoundChat
forall x. RemoveRecentlyFoundChat -> Rep RemoveRecentlyFoundChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveRecentlyFoundChat x -> RemoveRecentlyFoundChat
$cfrom :: forall x. RemoveRecentlyFoundChat -> Rep RemoveRecentlyFoundChat x
Generic)

-- | Parameter of Function clearRecentlyFoundChats
data ClearRecentlyFoundChats
  = -- | Clears the list of recently found chats
    ClearRecentlyFoundChats
      {
      }
  deriving (Int -> ClearRecentlyFoundChats -> ShowS
[ClearRecentlyFoundChats] -> ShowS
ClearRecentlyFoundChats -> String
(Int -> ClearRecentlyFoundChats -> ShowS)
-> (ClearRecentlyFoundChats -> String)
-> ([ClearRecentlyFoundChats] -> ShowS)
-> Show ClearRecentlyFoundChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearRecentlyFoundChats] -> ShowS
$cshowList :: [ClearRecentlyFoundChats] -> ShowS
show :: ClearRecentlyFoundChats -> String
$cshow :: ClearRecentlyFoundChats -> String
showsPrec :: Int -> ClearRecentlyFoundChats -> ShowS
$cshowsPrec :: Int -> ClearRecentlyFoundChats -> ShowS
Show, ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool
(ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool)
-> (ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool)
-> Eq ClearRecentlyFoundChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool
$c/= :: ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool
== :: ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool
$c== :: ClearRecentlyFoundChats -> ClearRecentlyFoundChats -> Bool
Eq, (forall x.
 ClearRecentlyFoundChats -> Rep ClearRecentlyFoundChats x)
-> (forall x.
    Rep ClearRecentlyFoundChats x -> ClearRecentlyFoundChats)
-> Generic ClearRecentlyFoundChats
forall x. Rep ClearRecentlyFoundChats x -> ClearRecentlyFoundChats
forall x. ClearRecentlyFoundChats -> Rep ClearRecentlyFoundChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClearRecentlyFoundChats x -> ClearRecentlyFoundChats
$cfrom :: forall x. ClearRecentlyFoundChats -> Rep ClearRecentlyFoundChats x
Generic)

-- | Parameter of Function checkChatUsername
data CheckChatUsername
  = -- | Checks whether a username can be set for a chat
    CheckChatUsername
      { -- | Chat identifier; should be identifier of a supergroup chat, or a channel chat, or a private chat with self, or zero if chat is being created
        CheckChatUsername -> Int
chat_id :: I53,
        -- | Username to be checked
        CheckChatUsername -> T
username :: T
      }
  deriving (Int -> CheckChatUsername -> ShowS
[CheckChatUsername] -> ShowS
CheckChatUsername -> String
(Int -> CheckChatUsername -> ShowS)
-> (CheckChatUsername -> String)
-> ([CheckChatUsername] -> ShowS)
-> Show CheckChatUsername
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckChatUsername] -> ShowS
$cshowList :: [CheckChatUsername] -> ShowS
show :: CheckChatUsername -> String
$cshow :: CheckChatUsername -> String
showsPrec :: Int -> CheckChatUsername -> ShowS
$cshowsPrec :: Int -> CheckChatUsername -> ShowS
Show, CheckChatUsername -> CheckChatUsername -> Bool
(CheckChatUsername -> CheckChatUsername -> Bool)
-> (CheckChatUsername -> CheckChatUsername -> Bool)
-> Eq CheckChatUsername
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckChatUsername -> CheckChatUsername -> Bool
$c/= :: CheckChatUsername -> CheckChatUsername -> Bool
== :: CheckChatUsername -> CheckChatUsername -> Bool
$c== :: CheckChatUsername -> CheckChatUsername -> Bool
Eq, (forall x. CheckChatUsername -> Rep CheckChatUsername x)
-> (forall x. Rep CheckChatUsername x -> CheckChatUsername)
-> Generic CheckChatUsername
forall x. Rep CheckChatUsername x -> CheckChatUsername
forall x. CheckChatUsername -> Rep CheckChatUsername x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckChatUsername x -> CheckChatUsername
$cfrom :: forall x. CheckChatUsername -> Rep CheckChatUsername x
Generic)

-- | Parameter of Function getCreatedPublicChats
data GetCreatedPublicChats
  = -- | Returns a list of public chats of the specified type, owned by the user
    GetCreatedPublicChats
      { -- | Type of the public chats to return
        GetCreatedPublicChats -> PublicChatType
type_ :: PublicChatType
      }
  deriving (Int -> GetCreatedPublicChats -> ShowS
[GetCreatedPublicChats] -> ShowS
GetCreatedPublicChats -> String
(Int -> GetCreatedPublicChats -> ShowS)
-> (GetCreatedPublicChats -> String)
-> ([GetCreatedPublicChats] -> ShowS)
-> Show GetCreatedPublicChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCreatedPublicChats] -> ShowS
$cshowList :: [GetCreatedPublicChats] -> ShowS
show :: GetCreatedPublicChats -> String
$cshow :: GetCreatedPublicChats -> String
showsPrec :: Int -> GetCreatedPublicChats -> ShowS
$cshowsPrec :: Int -> GetCreatedPublicChats -> ShowS
Show, GetCreatedPublicChats -> GetCreatedPublicChats -> Bool
(GetCreatedPublicChats -> GetCreatedPublicChats -> Bool)
-> (GetCreatedPublicChats -> GetCreatedPublicChats -> Bool)
-> Eq GetCreatedPublicChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCreatedPublicChats -> GetCreatedPublicChats -> Bool
$c/= :: GetCreatedPublicChats -> GetCreatedPublicChats -> Bool
== :: GetCreatedPublicChats -> GetCreatedPublicChats -> Bool
$c== :: GetCreatedPublicChats -> GetCreatedPublicChats -> Bool
Eq, (forall x. GetCreatedPublicChats -> Rep GetCreatedPublicChats x)
-> (forall x. Rep GetCreatedPublicChats x -> GetCreatedPublicChats)
-> Generic GetCreatedPublicChats
forall x. Rep GetCreatedPublicChats x -> GetCreatedPublicChats
forall x. GetCreatedPublicChats -> Rep GetCreatedPublicChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCreatedPublicChats x -> GetCreatedPublicChats
$cfrom :: forall x. GetCreatedPublicChats -> Rep GetCreatedPublicChats x
Generic)

-- | Parameter of Function checkCreatedPublicChatsLimit
data CheckCreatedPublicChatsLimit
  = -- | Checks whether the maximum number of owned public chats has been reached. Returns corresponding error if the limit was reached
    CheckCreatedPublicChatsLimit
      { -- | Type of the public chats, for which to check the limit
        CheckCreatedPublicChatsLimit -> PublicChatType
type_ :: PublicChatType
      }
  deriving (Int -> CheckCreatedPublicChatsLimit -> ShowS
[CheckCreatedPublicChatsLimit] -> ShowS
CheckCreatedPublicChatsLimit -> String
(Int -> CheckCreatedPublicChatsLimit -> ShowS)
-> (CheckCreatedPublicChatsLimit -> String)
-> ([CheckCreatedPublicChatsLimit] -> ShowS)
-> Show CheckCreatedPublicChatsLimit
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckCreatedPublicChatsLimit] -> ShowS
$cshowList :: [CheckCreatedPublicChatsLimit] -> ShowS
show :: CheckCreatedPublicChatsLimit -> String
$cshow :: CheckCreatedPublicChatsLimit -> String
showsPrec :: Int -> CheckCreatedPublicChatsLimit -> ShowS
$cshowsPrec :: Int -> CheckCreatedPublicChatsLimit -> ShowS
Show, CheckCreatedPublicChatsLimit
-> CheckCreatedPublicChatsLimit -> Bool
(CheckCreatedPublicChatsLimit
 -> CheckCreatedPublicChatsLimit -> Bool)
-> (CheckCreatedPublicChatsLimit
    -> CheckCreatedPublicChatsLimit -> Bool)
-> Eq CheckCreatedPublicChatsLimit
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckCreatedPublicChatsLimit
-> CheckCreatedPublicChatsLimit -> Bool
$c/= :: CheckCreatedPublicChatsLimit
-> CheckCreatedPublicChatsLimit -> Bool
== :: CheckCreatedPublicChatsLimit
-> CheckCreatedPublicChatsLimit -> Bool
$c== :: CheckCreatedPublicChatsLimit
-> CheckCreatedPublicChatsLimit -> Bool
Eq, (forall x.
 CheckCreatedPublicChatsLimit -> Rep CheckCreatedPublicChatsLimit x)
-> (forall x.
    Rep CheckCreatedPublicChatsLimit x -> CheckCreatedPublicChatsLimit)
-> Generic CheckCreatedPublicChatsLimit
forall x.
Rep CheckCreatedPublicChatsLimit x -> CheckCreatedPublicChatsLimit
forall x.
CheckCreatedPublicChatsLimit -> Rep CheckCreatedPublicChatsLimit x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckCreatedPublicChatsLimit x -> CheckCreatedPublicChatsLimit
$cfrom :: forall x.
CheckCreatedPublicChatsLimit -> Rep CheckCreatedPublicChatsLimit x
Generic)

-- | Parameter of Function getSuitableDiscussionChats
data GetSuitableDiscussionChats
  = -- | Returns a list of basic group and supergroup chats, which can be used as a discussion group for a channel. Basic group chats need to be first upgraded to supergroups before they can be set as a discussion group
    GetSuitableDiscussionChats
      {
      }
  deriving (Int -> GetSuitableDiscussionChats -> ShowS
[GetSuitableDiscussionChats] -> ShowS
GetSuitableDiscussionChats -> String
(Int -> GetSuitableDiscussionChats -> ShowS)
-> (GetSuitableDiscussionChats -> String)
-> ([GetSuitableDiscussionChats] -> ShowS)
-> Show GetSuitableDiscussionChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSuitableDiscussionChats] -> ShowS
$cshowList :: [GetSuitableDiscussionChats] -> ShowS
show :: GetSuitableDiscussionChats -> String
$cshow :: GetSuitableDiscussionChats -> String
showsPrec :: Int -> GetSuitableDiscussionChats -> ShowS
$cshowsPrec :: Int -> GetSuitableDiscussionChats -> ShowS
Show, GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool
(GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool)
-> (GetSuitableDiscussionChats
    -> GetSuitableDiscussionChats -> Bool)
-> Eq GetSuitableDiscussionChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool
$c/= :: GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool
== :: GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool
$c== :: GetSuitableDiscussionChats -> GetSuitableDiscussionChats -> Bool
Eq, (forall x.
 GetSuitableDiscussionChats -> Rep GetSuitableDiscussionChats x)
-> (forall x.
    Rep GetSuitableDiscussionChats x -> GetSuitableDiscussionChats)
-> Generic GetSuitableDiscussionChats
forall x.
Rep GetSuitableDiscussionChats x -> GetSuitableDiscussionChats
forall x.
GetSuitableDiscussionChats -> Rep GetSuitableDiscussionChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSuitableDiscussionChats x -> GetSuitableDiscussionChats
$cfrom :: forall x.
GetSuitableDiscussionChats -> Rep GetSuitableDiscussionChats x
Generic)

-- | Parameter of Function getInactiveSupergroupChats
data GetInactiveSupergroupChats
  = -- | Returns a list of recently inactive supergroups and channels. Can be used when user reaches limit on the number of joined supergroups and channels and receives CHANNELS_TOO_MUCH error
    GetInactiveSupergroupChats
      {
      }
  deriving (Int -> GetInactiveSupergroupChats -> ShowS
[GetInactiveSupergroupChats] -> ShowS
GetInactiveSupergroupChats -> String
(Int -> GetInactiveSupergroupChats -> ShowS)
-> (GetInactiveSupergroupChats -> String)
-> ([GetInactiveSupergroupChats] -> ShowS)
-> Show GetInactiveSupergroupChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInactiveSupergroupChats] -> ShowS
$cshowList :: [GetInactiveSupergroupChats] -> ShowS
show :: GetInactiveSupergroupChats -> String
$cshow :: GetInactiveSupergroupChats -> String
showsPrec :: Int -> GetInactiveSupergroupChats -> ShowS
$cshowsPrec :: Int -> GetInactiveSupergroupChats -> ShowS
Show, GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool
(GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool)
-> (GetInactiveSupergroupChats
    -> GetInactiveSupergroupChats -> Bool)
-> Eq GetInactiveSupergroupChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool
$c/= :: GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool
== :: GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool
$c== :: GetInactiveSupergroupChats -> GetInactiveSupergroupChats -> Bool
Eq, (forall x.
 GetInactiveSupergroupChats -> Rep GetInactiveSupergroupChats x)
-> (forall x.
    Rep GetInactiveSupergroupChats x -> GetInactiveSupergroupChats)
-> Generic GetInactiveSupergroupChats
forall x.
Rep GetInactiveSupergroupChats x -> GetInactiveSupergroupChats
forall x.
GetInactiveSupergroupChats -> Rep GetInactiveSupergroupChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetInactiveSupergroupChats x -> GetInactiveSupergroupChats
$cfrom :: forall x.
GetInactiveSupergroupChats -> Rep GetInactiveSupergroupChats x
Generic)

-- | Parameter of Function getGroupsInCommon
data GetGroupsInCommon
  = -- | Returns a list of common group chats with a given user. Chats are sorted by their type and creation date
    GetGroupsInCommon
      { -- | User identifier
        GetGroupsInCommon -> Int
user_id :: I32,
        -- | Chat identifier starting from which to return chats; use 0 for the first request
        GetGroupsInCommon -> Int
offset_chat_id :: I53,
        -- | The maximum number of chats to be returned; up to 100
        GetGroupsInCommon -> Int
limit :: I32
      }
  deriving (Int -> GetGroupsInCommon -> ShowS
[GetGroupsInCommon] -> ShowS
GetGroupsInCommon -> String
(Int -> GetGroupsInCommon -> ShowS)
-> (GetGroupsInCommon -> String)
-> ([GetGroupsInCommon] -> ShowS)
-> Show GetGroupsInCommon
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGroupsInCommon] -> ShowS
$cshowList :: [GetGroupsInCommon] -> ShowS
show :: GetGroupsInCommon -> String
$cshow :: GetGroupsInCommon -> String
showsPrec :: Int -> GetGroupsInCommon -> ShowS
$cshowsPrec :: Int -> GetGroupsInCommon -> ShowS
Show, GetGroupsInCommon -> GetGroupsInCommon -> Bool
(GetGroupsInCommon -> GetGroupsInCommon -> Bool)
-> (GetGroupsInCommon -> GetGroupsInCommon -> Bool)
-> Eq GetGroupsInCommon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGroupsInCommon -> GetGroupsInCommon -> Bool
$c/= :: GetGroupsInCommon -> GetGroupsInCommon -> Bool
== :: GetGroupsInCommon -> GetGroupsInCommon -> Bool
$c== :: GetGroupsInCommon -> GetGroupsInCommon -> Bool
Eq, (forall x. GetGroupsInCommon -> Rep GetGroupsInCommon x)
-> (forall x. Rep GetGroupsInCommon x -> GetGroupsInCommon)
-> Generic GetGroupsInCommon
forall x. Rep GetGroupsInCommon x -> GetGroupsInCommon
forall x. GetGroupsInCommon -> Rep GetGroupsInCommon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGroupsInCommon x -> GetGroupsInCommon
$cfrom :: forall x. GetGroupsInCommon -> Rep GetGroupsInCommon x
Generic)

-- | Parameter of Function getChatHistory
data GetChatHistory
  = -- | Returns messages in a chat. The messages are returned in a reverse chronological order (i.e., in order of decreasing message_id).
    GetChatHistory
      { -- | Chat identifier
        GetChatHistory -> Int
chat_id :: I53,
        -- | Identifier of the message starting from which history must be fetched; use 0 to get results from the last message
        GetChatHistory -> Int
from_message_id :: I53,
        -- | Specify 0 to get results from exactly the from_message_id or a negative offset up to 99 to get additionally some newer messages
        GetChatHistory -> Int
offset :: I32,
        -- | The maximum number of messages to be returned; must be positive and can't be greater than 100. If the offset is negative, the limit must be greater or equal to -offset. Fewer messages may be returned than specified by the limit, even if the end of the message history has not been reached
        GetChatHistory -> Int
limit :: I32,
        -- | If true, returns only messages that are available locally without sending network requests
        GetChatHistory -> Bool
only_local :: Bool
      }
  deriving (Int -> GetChatHistory -> ShowS
[GetChatHistory] -> ShowS
GetChatHistory -> String
(Int -> GetChatHistory -> ShowS)
-> (GetChatHistory -> String)
-> ([GetChatHistory] -> ShowS)
-> Show GetChatHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatHistory] -> ShowS
$cshowList :: [GetChatHistory] -> ShowS
show :: GetChatHistory -> String
$cshow :: GetChatHistory -> String
showsPrec :: Int -> GetChatHistory -> ShowS
$cshowsPrec :: Int -> GetChatHistory -> ShowS
Show, GetChatHistory -> GetChatHistory -> Bool
(GetChatHistory -> GetChatHistory -> Bool)
-> (GetChatHistory -> GetChatHistory -> Bool) -> Eq GetChatHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatHistory -> GetChatHistory -> Bool
$c/= :: GetChatHistory -> GetChatHistory -> Bool
== :: GetChatHistory -> GetChatHistory -> Bool
$c== :: GetChatHistory -> GetChatHistory -> Bool
Eq, (forall x. GetChatHistory -> Rep GetChatHistory x)
-> (forall x. Rep GetChatHistory x -> GetChatHistory)
-> Generic GetChatHistory
forall x. Rep GetChatHistory x -> GetChatHistory
forall x. GetChatHistory -> Rep GetChatHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatHistory x -> GetChatHistory
$cfrom :: forall x. GetChatHistory -> Rep GetChatHistory x
Generic)

-- | Parameter of Function deleteChatHistory
data DeleteChatHistory
  = -- | Deletes all messages in the chat. Use Chat.can_be_deleted_only_for_self and Chat.can_be_deleted_for_all_users fields to find whether and how the method can be applied to the chat
    DeleteChatHistory
      { -- | Chat identifier
        DeleteChatHistory -> Int
chat_id :: I53,
        -- | Pass true if the chat should be removed from the chat list
        DeleteChatHistory -> Bool
remove_from_chat_list :: Bool,
        -- | Pass true to try to delete chat history for all users
        DeleteChatHistory -> Bool
revoke :: Bool
      }
  deriving (Int -> DeleteChatHistory -> ShowS
[DeleteChatHistory] -> ShowS
DeleteChatHistory -> String
(Int -> DeleteChatHistory -> ShowS)
-> (DeleteChatHistory -> String)
-> ([DeleteChatHistory] -> ShowS)
-> Show DeleteChatHistory
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteChatHistory] -> ShowS
$cshowList :: [DeleteChatHistory] -> ShowS
show :: DeleteChatHistory -> String
$cshow :: DeleteChatHistory -> String
showsPrec :: Int -> DeleteChatHistory -> ShowS
$cshowsPrec :: Int -> DeleteChatHistory -> ShowS
Show, DeleteChatHistory -> DeleteChatHistory -> Bool
(DeleteChatHistory -> DeleteChatHistory -> Bool)
-> (DeleteChatHistory -> DeleteChatHistory -> Bool)
-> Eq DeleteChatHistory
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteChatHistory -> DeleteChatHistory -> Bool
$c/= :: DeleteChatHistory -> DeleteChatHistory -> Bool
== :: DeleteChatHistory -> DeleteChatHistory -> Bool
$c== :: DeleteChatHistory -> DeleteChatHistory -> Bool
Eq, (forall x. DeleteChatHistory -> Rep DeleteChatHistory x)
-> (forall x. Rep DeleteChatHistory x -> DeleteChatHistory)
-> Generic DeleteChatHistory
forall x. Rep DeleteChatHistory x -> DeleteChatHistory
forall x. DeleteChatHistory -> Rep DeleteChatHistory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteChatHistory x -> DeleteChatHistory
$cfrom :: forall x. DeleteChatHistory -> Rep DeleteChatHistory x
Generic)

-- | Parameter of Function searchChatMessages
data SearchChatMessages
  = -- | Searches for messages with given words in the chat. Returns the results in reverse chronological order, i.e. in order of decreasing message_id. Cannot be used in secret chats with a non-empty query
    SearchChatMessages
      { -- | Identifier of the chat in which to search messages
        SearchChatMessages -> Int
chat_id :: I53,
        -- | Query to search for
        SearchChatMessages -> T
query :: T,
        -- | If not 0, only messages sent by the specified user will be returned. Not supported in secret chats
        SearchChatMessages -> Int
sender_user_id :: I32,
        -- | Identifier of the message starting from which history must be fetched; use 0 to get results from the last message
        SearchChatMessages -> Int
from_message_id :: I53,
        -- | Specify 0 to get results from exactly the from_message_id or a negative offset to get the specified message and some newer messages
        SearchChatMessages -> Int
offset :: I32,
        -- | The maximum number of messages to be returned; must be positive and can't be greater than 100. If the offset is negative, the limit must be greater than -offset. Fewer messages may be returned than specified by the limit, even if the end of the message history has not been reached
        SearchChatMessages -> Int
limit :: I32,
        -- | Filter for message content in the search results
        SearchChatMessages -> SearchMessagesFilter
filter :: SearchMessagesFilter
      }
  deriving (Int -> SearchChatMessages -> ShowS
[SearchChatMessages] -> ShowS
SearchChatMessages -> String
(Int -> SearchChatMessages -> ShowS)
-> (SearchChatMessages -> String)
-> ([SearchChatMessages] -> ShowS)
-> Show SearchChatMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChatMessages] -> ShowS
$cshowList :: [SearchChatMessages] -> ShowS
show :: SearchChatMessages -> String
$cshow :: SearchChatMessages -> String
showsPrec :: Int -> SearchChatMessages -> ShowS
$cshowsPrec :: Int -> SearchChatMessages -> ShowS
Show, SearchChatMessages -> SearchChatMessages -> Bool
(SearchChatMessages -> SearchChatMessages -> Bool)
-> (SearchChatMessages -> SearchChatMessages -> Bool)
-> Eq SearchChatMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChatMessages -> SearchChatMessages -> Bool
$c/= :: SearchChatMessages -> SearchChatMessages -> Bool
== :: SearchChatMessages -> SearchChatMessages -> Bool
$c== :: SearchChatMessages -> SearchChatMessages -> Bool
Eq, (forall x. SearchChatMessages -> Rep SearchChatMessages x)
-> (forall x. Rep SearchChatMessages x -> SearchChatMessages)
-> Generic SearchChatMessages
forall x. Rep SearchChatMessages x -> SearchChatMessages
forall x. SearchChatMessages -> Rep SearchChatMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchChatMessages x -> SearchChatMessages
$cfrom :: forall x. SearchChatMessages -> Rep SearchChatMessages x
Generic)

-- | Parameter of Function searchMessages
data SearchMessages
  = -- | Searches for messages in all chats except secret chats. Returns the results in reverse chronological order (i.e., in order of decreasing (date, chat_id, message_id)).
    SearchMessages
      { -- | Chat list in which to search messages; pass null to search in all chats regardless of their chat list
        SearchMessages -> ChatList
chat_list :: ChatList,
        -- | Query to search for
        SearchMessages -> T
query :: T,
        -- | The date of the message starting from which the results should be fetched. Use 0 or any date in the future to get results from the last message
        SearchMessages -> Int
offset_date :: I32,
        -- | The chat identifier of the last found message, or 0 for the first request
        SearchMessages -> Int
offset_chat_id :: I53,
        -- | The message identifier of the last found message, or 0 for the first request
        SearchMessages -> Int
offset_message_id :: I53,
        -- | The maximum number of messages to be returned, up to 100. Fewer messages may be returned than specified by the limit, even if the end of the message history has not been reached
        SearchMessages -> Int
limit :: I32
      }
  deriving (Int -> SearchMessages -> ShowS
[SearchMessages] -> ShowS
SearchMessages -> String
(Int -> SearchMessages -> ShowS)
-> (SearchMessages -> String)
-> ([SearchMessages] -> ShowS)
-> Show SearchMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchMessages] -> ShowS
$cshowList :: [SearchMessages] -> ShowS
show :: SearchMessages -> String
$cshow :: SearchMessages -> String
showsPrec :: Int -> SearchMessages -> ShowS
$cshowsPrec :: Int -> SearchMessages -> ShowS
Show, SearchMessages -> SearchMessages -> Bool
(SearchMessages -> SearchMessages -> Bool)
-> (SearchMessages -> SearchMessages -> Bool) -> Eq SearchMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchMessages -> SearchMessages -> Bool
$c/= :: SearchMessages -> SearchMessages -> Bool
== :: SearchMessages -> SearchMessages -> Bool
$c== :: SearchMessages -> SearchMessages -> Bool
Eq, (forall x. SearchMessages -> Rep SearchMessages x)
-> (forall x. Rep SearchMessages x -> SearchMessages)
-> Generic SearchMessages
forall x. Rep SearchMessages x -> SearchMessages
forall x. SearchMessages -> Rep SearchMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchMessages x -> SearchMessages
$cfrom :: forall x. SearchMessages -> Rep SearchMessages x
Generic)

-- | Parameter of Function searchSecretMessages
data SearchSecretMessages
  = -- | Searches for messages in secret chats. Returns the results in reverse chronological order. For optimal performance the number of returned messages is chosen by the library
    SearchSecretMessages
      { -- | Identifier of the chat in which to search. Specify 0 to search in all secret chats
        SearchSecretMessages -> Int
chat_id :: I53,
        -- | Query to search for. If empty, searchChatMessages should be used instead
        SearchSecretMessages -> T
query :: T,
        -- | The identifier from the result of a previous request, use 0 to get results from the last message
        SearchSecretMessages -> I64
from_search_id :: I64,
        -- | The maximum number of messages to be returned; up to 100. Fewer messages may be returned than specified by the limit, even if the end of the message history has not been reached
        SearchSecretMessages -> Int
limit :: I32,
        -- | A filter for the content of messages in the search results
        SearchSecretMessages -> SearchMessagesFilter
filter :: SearchMessagesFilter
      }
  deriving (Int -> SearchSecretMessages -> ShowS
[SearchSecretMessages] -> ShowS
SearchSecretMessages -> String
(Int -> SearchSecretMessages -> ShowS)
-> (SearchSecretMessages -> String)
-> ([SearchSecretMessages] -> ShowS)
-> Show SearchSecretMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchSecretMessages] -> ShowS
$cshowList :: [SearchSecretMessages] -> ShowS
show :: SearchSecretMessages -> String
$cshow :: SearchSecretMessages -> String
showsPrec :: Int -> SearchSecretMessages -> ShowS
$cshowsPrec :: Int -> SearchSecretMessages -> ShowS
Show, SearchSecretMessages -> SearchSecretMessages -> Bool
(SearchSecretMessages -> SearchSecretMessages -> Bool)
-> (SearchSecretMessages -> SearchSecretMessages -> Bool)
-> Eq SearchSecretMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchSecretMessages -> SearchSecretMessages -> Bool
$c/= :: SearchSecretMessages -> SearchSecretMessages -> Bool
== :: SearchSecretMessages -> SearchSecretMessages -> Bool
$c== :: SearchSecretMessages -> SearchSecretMessages -> Bool
Eq, (forall x. SearchSecretMessages -> Rep SearchSecretMessages x)
-> (forall x. Rep SearchSecretMessages x -> SearchSecretMessages)
-> Generic SearchSecretMessages
forall x. Rep SearchSecretMessages x -> SearchSecretMessages
forall x. SearchSecretMessages -> Rep SearchSecretMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchSecretMessages x -> SearchSecretMessages
$cfrom :: forall x. SearchSecretMessages -> Rep SearchSecretMessages x
Generic)

-- | Parameter of Function searchCallMessages
data SearchCallMessages
  = -- | Searches for call messages. Returns the results in reverse chronological order (i. e., in order of decreasing message_id). For optimal performance the number of returned messages is chosen by the library
    SearchCallMessages
      { -- | Identifier of the message from which to search; use 0 to get results from the last message
        SearchCallMessages -> Int
from_message_id :: I53,
        -- | The maximum number of messages to be returned; up to 100. Fewer messages may be returned than specified by the limit, even if the end of the message history has not been reached
        SearchCallMessages -> Int
limit :: I32,
        -- | If true, returns only messages with missed calls
        SearchCallMessages -> Bool
only_missed :: Bool
      }
  deriving (Int -> SearchCallMessages -> ShowS
[SearchCallMessages] -> ShowS
SearchCallMessages -> String
(Int -> SearchCallMessages -> ShowS)
-> (SearchCallMessages -> String)
-> ([SearchCallMessages] -> ShowS)
-> Show SearchCallMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchCallMessages] -> ShowS
$cshowList :: [SearchCallMessages] -> ShowS
show :: SearchCallMessages -> String
$cshow :: SearchCallMessages -> String
showsPrec :: Int -> SearchCallMessages -> ShowS
$cshowsPrec :: Int -> SearchCallMessages -> ShowS
Show, SearchCallMessages -> SearchCallMessages -> Bool
(SearchCallMessages -> SearchCallMessages -> Bool)
-> (SearchCallMessages -> SearchCallMessages -> Bool)
-> Eq SearchCallMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchCallMessages -> SearchCallMessages -> Bool
$c/= :: SearchCallMessages -> SearchCallMessages -> Bool
== :: SearchCallMessages -> SearchCallMessages -> Bool
$c== :: SearchCallMessages -> SearchCallMessages -> Bool
Eq, (forall x. SearchCallMessages -> Rep SearchCallMessages x)
-> (forall x. Rep SearchCallMessages x -> SearchCallMessages)
-> Generic SearchCallMessages
forall x. Rep SearchCallMessages x -> SearchCallMessages
forall x. SearchCallMessages -> Rep SearchCallMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchCallMessages x -> SearchCallMessages
$cfrom :: forall x. SearchCallMessages -> Rep SearchCallMessages x
Generic)

-- | Parameter of Function searchChatRecentLocationMessages
data SearchChatRecentLocationMessages
  = -- | Returns information about the recent locations of chat members that were sent to the chat. Returns up to 1 location message per user
    SearchChatRecentLocationMessages
      { -- | Chat identifier
        SearchChatRecentLocationMessages -> Int
chat_id :: I53,
        -- | The maximum number of messages to be returned
        SearchChatRecentLocationMessages -> Int
limit :: I32
      }
  deriving (Int -> SearchChatRecentLocationMessages -> ShowS
[SearchChatRecentLocationMessages] -> ShowS
SearchChatRecentLocationMessages -> String
(Int -> SearchChatRecentLocationMessages -> ShowS)
-> (SearchChatRecentLocationMessages -> String)
-> ([SearchChatRecentLocationMessages] -> ShowS)
-> Show SearchChatRecentLocationMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChatRecentLocationMessages] -> ShowS
$cshowList :: [SearchChatRecentLocationMessages] -> ShowS
show :: SearchChatRecentLocationMessages -> String
$cshow :: SearchChatRecentLocationMessages -> String
showsPrec :: Int -> SearchChatRecentLocationMessages -> ShowS
$cshowsPrec :: Int -> SearchChatRecentLocationMessages -> ShowS
Show, SearchChatRecentLocationMessages
-> SearchChatRecentLocationMessages -> Bool
(SearchChatRecentLocationMessages
 -> SearchChatRecentLocationMessages -> Bool)
-> (SearchChatRecentLocationMessages
    -> SearchChatRecentLocationMessages -> Bool)
-> Eq SearchChatRecentLocationMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChatRecentLocationMessages
-> SearchChatRecentLocationMessages -> Bool
$c/= :: SearchChatRecentLocationMessages
-> SearchChatRecentLocationMessages -> Bool
== :: SearchChatRecentLocationMessages
-> SearchChatRecentLocationMessages -> Bool
$c== :: SearchChatRecentLocationMessages
-> SearchChatRecentLocationMessages -> Bool
Eq, (forall x.
 SearchChatRecentLocationMessages
 -> Rep SearchChatRecentLocationMessages x)
-> (forall x.
    Rep SearchChatRecentLocationMessages x
    -> SearchChatRecentLocationMessages)
-> Generic SearchChatRecentLocationMessages
forall x.
Rep SearchChatRecentLocationMessages x
-> SearchChatRecentLocationMessages
forall x.
SearchChatRecentLocationMessages
-> Rep SearchChatRecentLocationMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchChatRecentLocationMessages x
-> SearchChatRecentLocationMessages
$cfrom :: forall x.
SearchChatRecentLocationMessages
-> Rep SearchChatRecentLocationMessages x
Generic)

-- | Parameter of Function getActiveLiveLocationMessages
data GetActiveLiveLocationMessages
  = -- | Returns all active live locations that should be updated by the client. The list is persistent across application restarts only if the message database is used
    GetActiveLiveLocationMessages
      {
      }
  deriving (Int -> GetActiveLiveLocationMessages -> ShowS
[GetActiveLiveLocationMessages] -> ShowS
GetActiveLiveLocationMessages -> String
(Int -> GetActiveLiveLocationMessages -> ShowS)
-> (GetActiveLiveLocationMessages -> String)
-> ([GetActiveLiveLocationMessages] -> ShowS)
-> Show GetActiveLiveLocationMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetActiveLiveLocationMessages] -> ShowS
$cshowList :: [GetActiveLiveLocationMessages] -> ShowS
show :: GetActiveLiveLocationMessages -> String
$cshow :: GetActiveLiveLocationMessages -> String
showsPrec :: Int -> GetActiveLiveLocationMessages -> ShowS
$cshowsPrec :: Int -> GetActiveLiveLocationMessages -> ShowS
Show, GetActiveLiveLocationMessages
-> GetActiveLiveLocationMessages -> Bool
(GetActiveLiveLocationMessages
 -> GetActiveLiveLocationMessages -> Bool)
-> (GetActiveLiveLocationMessages
    -> GetActiveLiveLocationMessages -> Bool)
-> Eq GetActiveLiveLocationMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetActiveLiveLocationMessages
-> GetActiveLiveLocationMessages -> Bool
$c/= :: GetActiveLiveLocationMessages
-> GetActiveLiveLocationMessages -> Bool
== :: GetActiveLiveLocationMessages
-> GetActiveLiveLocationMessages -> Bool
$c== :: GetActiveLiveLocationMessages
-> GetActiveLiveLocationMessages -> Bool
Eq, (forall x.
 GetActiveLiveLocationMessages
 -> Rep GetActiveLiveLocationMessages x)
-> (forall x.
    Rep GetActiveLiveLocationMessages x
    -> GetActiveLiveLocationMessages)
-> Generic GetActiveLiveLocationMessages
forall x.
Rep GetActiveLiveLocationMessages x
-> GetActiveLiveLocationMessages
forall x.
GetActiveLiveLocationMessages
-> Rep GetActiveLiveLocationMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetActiveLiveLocationMessages x
-> GetActiveLiveLocationMessages
$cfrom :: forall x.
GetActiveLiveLocationMessages
-> Rep GetActiveLiveLocationMessages x
Generic)

-- | Parameter of Function getChatMessageByDate
data GetChatMessageByDate
  = -- | Returns the last message sent in a chat no later than the specified date
    GetChatMessageByDate
      { -- | Chat identifier
        GetChatMessageByDate -> Int
chat_id :: I53,
        -- | Point in time (Unix timestamp) relative to which to search for messages
        GetChatMessageByDate -> Int
date :: I32
      }
  deriving (Int -> GetChatMessageByDate -> ShowS
[GetChatMessageByDate] -> ShowS
GetChatMessageByDate -> String
(Int -> GetChatMessageByDate -> ShowS)
-> (GetChatMessageByDate -> String)
-> ([GetChatMessageByDate] -> ShowS)
-> Show GetChatMessageByDate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatMessageByDate] -> ShowS
$cshowList :: [GetChatMessageByDate] -> ShowS
show :: GetChatMessageByDate -> String
$cshow :: GetChatMessageByDate -> String
showsPrec :: Int -> GetChatMessageByDate -> ShowS
$cshowsPrec :: Int -> GetChatMessageByDate -> ShowS
Show, GetChatMessageByDate -> GetChatMessageByDate -> Bool
(GetChatMessageByDate -> GetChatMessageByDate -> Bool)
-> (GetChatMessageByDate -> GetChatMessageByDate -> Bool)
-> Eq GetChatMessageByDate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatMessageByDate -> GetChatMessageByDate -> Bool
$c/= :: GetChatMessageByDate -> GetChatMessageByDate -> Bool
== :: GetChatMessageByDate -> GetChatMessageByDate -> Bool
$c== :: GetChatMessageByDate -> GetChatMessageByDate -> Bool
Eq, (forall x. GetChatMessageByDate -> Rep GetChatMessageByDate x)
-> (forall x. Rep GetChatMessageByDate x -> GetChatMessageByDate)
-> Generic GetChatMessageByDate
forall x. Rep GetChatMessageByDate x -> GetChatMessageByDate
forall x. GetChatMessageByDate -> Rep GetChatMessageByDate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatMessageByDate x -> GetChatMessageByDate
$cfrom :: forall x. GetChatMessageByDate -> Rep GetChatMessageByDate x
Generic)

-- | Parameter of Function getChatMessageCount
data GetChatMessageCount
  = -- | Returns approximate number of messages of the specified type in the chat
    GetChatMessageCount
      { -- | Identifier of the chat in which to count messages
        GetChatMessageCount -> Int
chat_id :: I53,
        -- | Filter for message content; searchMessagesFilterEmpty is unsupported in this function
        GetChatMessageCount -> SearchMessagesFilter
filter :: SearchMessagesFilter,
        -- | If true, returns count that is available locally without sending network requests, returning -1 if the number of messages is unknown
        GetChatMessageCount -> Bool
return_local :: Bool
      }
  deriving (Int -> GetChatMessageCount -> ShowS
[GetChatMessageCount] -> ShowS
GetChatMessageCount -> String
(Int -> GetChatMessageCount -> ShowS)
-> (GetChatMessageCount -> String)
-> ([GetChatMessageCount] -> ShowS)
-> Show GetChatMessageCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatMessageCount] -> ShowS
$cshowList :: [GetChatMessageCount] -> ShowS
show :: GetChatMessageCount -> String
$cshow :: GetChatMessageCount -> String
showsPrec :: Int -> GetChatMessageCount -> ShowS
$cshowsPrec :: Int -> GetChatMessageCount -> ShowS
Show, GetChatMessageCount -> GetChatMessageCount -> Bool
(GetChatMessageCount -> GetChatMessageCount -> Bool)
-> (GetChatMessageCount -> GetChatMessageCount -> Bool)
-> Eq GetChatMessageCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatMessageCount -> GetChatMessageCount -> Bool
$c/= :: GetChatMessageCount -> GetChatMessageCount -> Bool
== :: GetChatMessageCount -> GetChatMessageCount -> Bool
$c== :: GetChatMessageCount -> GetChatMessageCount -> Bool
Eq, (forall x. GetChatMessageCount -> Rep GetChatMessageCount x)
-> (forall x. Rep GetChatMessageCount x -> GetChatMessageCount)
-> Generic GetChatMessageCount
forall x. Rep GetChatMessageCount x -> GetChatMessageCount
forall x. GetChatMessageCount -> Rep GetChatMessageCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatMessageCount x -> GetChatMessageCount
$cfrom :: forall x. GetChatMessageCount -> Rep GetChatMessageCount x
Generic)

-- | Parameter of Function getChatScheduledMessages
data GetChatScheduledMessages
  = -- | Returns all scheduled messages in a chat. The messages are returned in a reverse chronological order (i.e., in order of decreasing message_id)
    GetChatScheduledMessages
      { -- | Chat identifier
        GetChatScheduledMessages -> Int
chat_id :: I53
      }
  deriving (Int -> GetChatScheduledMessages -> ShowS
[GetChatScheduledMessages] -> ShowS
GetChatScheduledMessages -> String
(Int -> GetChatScheduledMessages -> ShowS)
-> (GetChatScheduledMessages -> String)
-> ([GetChatScheduledMessages] -> ShowS)
-> Show GetChatScheduledMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatScheduledMessages] -> ShowS
$cshowList :: [GetChatScheduledMessages] -> ShowS
show :: GetChatScheduledMessages -> String
$cshow :: GetChatScheduledMessages -> String
showsPrec :: Int -> GetChatScheduledMessages -> ShowS
$cshowsPrec :: Int -> GetChatScheduledMessages -> ShowS
Show, GetChatScheduledMessages -> GetChatScheduledMessages -> Bool
(GetChatScheduledMessages -> GetChatScheduledMessages -> Bool)
-> (GetChatScheduledMessages -> GetChatScheduledMessages -> Bool)
-> Eq GetChatScheduledMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatScheduledMessages -> GetChatScheduledMessages -> Bool
$c/= :: GetChatScheduledMessages -> GetChatScheduledMessages -> Bool
== :: GetChatScheduledMessages -> GetChatScheduledMessages -> Bool
$c== :: GetChatScheduledMessages -> GetChatScheduledMessages -> Bool
Eq, (forall x.
 GetChatScheduledMessages -> Rep GetChatScheduledMessages x)
-> (forall x.
    Rep GetChatScheduledMessages x -> GetChatScheduledMessages)
-> Generic GetChatScheduledMessages
forall x.
Rep GetChatScheduledMessages x -> GetChatScheduledMessages
forall x.
GetChatScheduledMessages -> Rep GetChatScheduledMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetChatScheduledMessages x -> GetChatScheduledMessages
$cfrom :: forall x.
GetChatScheduledMessages -> Rep GetChatScheduledMessages x
Generic)

-- | Parameter of Function removeNotification
data RemoveNotification
  = -- | Removes an active notification from notification list. Needs to be called only if the notification is removed by the current user
    RemoveNotification
      { -- | Identifier of notification group to which the notification belongs
        RemoveNotification -> Int
notification_group_id :: I32,
        -- | Identifier of removed notification
        RemoveNotification -> Int
notification_id :: I32
      }
  deriving (Int -> RemoveNotification -> ShowS
[RemoveNotification] -> ShowS
RemoveNotification -> String
(Int -> RemoveNotification -> ShowS)
-> (RemoveNotification -> String)
-> ([RemoveNotification] -> ShowS)
-> Show RemoveNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveNotification] -> ShowS
$cshowList :: [RemoveNotification] -> ShowS
show :: RemoveNotification -> String
$cshow :: RemoveNotification -> String
showsPrec :: Int -> RemoveNotification -> ShowS
$cshowsPrec :: Int -> RemoveNotification -> ShowS
Show, RemoveNotification -> RemoveNotification -> Bool
(RemoveNotification -> RemoveNotification -> Bool)
-> (RemoveNotification -> RemoveNotification -> Bool)
-> Eq RemoveNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveNotification -> RemoveNotification -> Bool
$c/= :: RemoveNotification -> RemoveNotification -> Bool
== :: RemoveNotification -> RemoveNotification -> Bool
$c== :: RemoveNotification -> RemoveNotification -> Bool
Eq, (forall x. RemoveNotification -> Rep RemoveNotification x)
-> (forall x. Rep RemoveNotification x -> RemoveNotification)
-> Generic RemoveNotification
forall x. Rep RemoveNotification x -> RemoveNotification
forall x. RemoveNotification -> Rep RemoveNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveNotification x -> RemoveNotification
$cfrom :: forall x. RemoveNotification -> Rep RemoveNotification x
Generic)

-- | Parameter of Function removeNotificationGroup
data RemoveNotificationGroup
  = -- | Removes a group of active notifications. Needs to be called only if the notification group is removed by the current user
    RemoveNotificationGroup
      { -- | Notification group identifier
        RemoveNotificationGroup -> Int
notification_group_id :: I32,
        -- | The maximum identifier of removed notifications
        RemoveNotificationGroup -> Int
max_notification_id :: I32
      }
  deriving (Int -> RemoveNotificationGroup -> ShowS
[RemoveNotificationGroup] -> ShowS
RemoveNotificationGroup -> String
(Int -> RemoveNotificationGroup -> ShowS)
-> (RemoveNotificationGroup -> String)
-> ([RemoveNotificationGroup] -> ShowS)
-> Show RemoveNotificationGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveNotificationGroup] -> ShowS
$cshowList :: [RemoveNotificationGroup] -> ShowS
show :: RemoveNotificationGroup -> String
$cshow :: RemoveNotificationGroup -> String
showsPrec :: Int -> RemoveNotificationGroup -> ShowS
$cshowsPrec :: Int -> RemoveNotificationGroup -> ShowS
Show, RemoveNotificationGroup -> RemoveNotificationGroup -> Bool
(RemoveNotificationGroup -> RemoveNotificationGroup -> Bool)
-> (RemoveNotificationGroup -> RemoveNotificationGroup -> Bool)
-> Eq RemoveNotificationGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveNotificationGroup -> RemoveNotificationGroup -> Bool
$c/= :: RemoveNotificationGroup -> RemoveNotificationGroup -> Bool
== :: RemoveNotificationGroup -> RemoveNotificationGroup -> Bool
$c== :: RemoveNotificationGroup -> RemoveNotificationGroup -> Bool
Eq, (forall x.
 RemoveNotificationGroup -> Rep RemoveNotificationGroup x)
-> (forall x.
    Rep RemoveNotificationGroup x -> RemoveNotificationGroup)
-> Generic RemoveNotificationGroup
forall x. Rep RemoveNotificationGroup x -> RemoveNotificationGroup
forall x. RemoveNotificationGroup -> Rep RemoveNotificationGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveNotificationGroup x -> RemoveNotificationGroup
$cfrom :: forall x. RemoveNotificationGroup -> Rep RemoveNotificationGroup x
Generic)

-- | Parameter of Function getPublicMessageLink
data GetPublicMessageLink
  = -- | Returns a public HTTPS link to a message. Available only for messages in supergroups and channels with a username
    GetPublicMessageLink
      { -- | Identifier of the chat to which the message belongs
        GetPublicMessageLink -> Int
chat_id :: I53,
        -- | Identifier of the message
        GetPublicMessageLink -> Int
message_id :: I53,
        -- | Pass true if a link for a whole media album should be returned
        GetPublicMessageLink -> Bool
for_album :: Bool
      }
  deriving (Int -> GetPublicMessageLink -> ShowS
[GetPublicMessageLink] -> ShowS
GetPublicMessageLink -> String
(Int -> GetPublicMessageLink -> ShowS)
-> (GetPublicMessageLink -> String)
-> ([GetPublicMessageLink] -> ShowS)
-> Show GetPublicMessageLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPublicMessageLink] -> ShowS
$cshowList :: [GetPublicMessageLink] -> ShowS
show :: GetPublicMessageLink -> String
$cshow :: GetPublicMessageLink -> String
showsPrec :: Int -> GetPublicMessageLink -> ShowS
$cshowsPrec :: Int -> GetPublicMessageLink -> ShowS
Show, GetPublicMessageLink -> GetPublicMessageLink -> Bool
(GetPublicMessageLink -> GetPublicMessageLink -> Bool)
-> (GetPublicMessageLink -> GetPublicMessageLink -> Bool)
-> Eq GetPublicMessageLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPublicMessageLink -> GetPublicMessageLink -> Bool
$c/= :: GetPublicMessageLink -> GetPublicMessageLink -> Bool
== :: GetPublicMessageLink -> GetPublicMessageLink -> Bool
$c== :: GetPublicMessageLink -> GetPublicMessageLink -> Bool
Eq, (forall x. GetPublicMessageLink -> Rep GetPublicMessageLink x)
-> (forall x. Rep GetPublicMessageLink x -> GetPublicMessageLink)
-> Generic GetPublicMessageLink
forall x. Rep GetPublicMessageLink x -> GetPublicMessageLink
forall x. GetPublicMessageLink -> Rep GetPublicMessageLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPublicMessageLink x -> GetPublicMessageLink
$cfrom :: forall x. GetPublicMessageLink -> Rep GetPublicMessageLink x
Generic)

-- | Parameter of Function getMessageLink
data GetMessageLink
  = -- | Returns a private HTTPS link to a message in a chat. Available only for already sent messages in supergroups and channels. The link will work only for members of the chat
    GetMessageLink
      { -- | Identifier of the chat to which the message belongs
        GetMessageLink -> Int
chat_id :: I53,
        -- | Identifier of the message
        GetMessageLink -> Int
message_id :: I53
      }
  deriving (Int -> GetMessageLink -> ShowS
[GetMessageLink] -> ShowS
GetMessageLink -> String
(Int -> GetMessageLink -> ShowS)
-> (GetMessageLink -> String)
-> ([GetMessageLink] -> ShowS)
-> Show GetMessageLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMessageLink] -> ShowS
$cshowList :: [GetMessageLink] -> ShowS
show :: GetMessageLink -> String
$cshow :: GetMessageLink -> String
showsPrec :: Int -> GetMessageLink -> ShowS
$cshowsPrec :: Int -> GetMessageLink -> ShowS
Show, GetMessageLink -> GetMessageLink -> Bool
(GetMessageLink -> GetMessageLink -> Bool)
-> (GetMessageLink -> GetMessageLink -> Bool) -> Eq GetMessageLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMessageLink -> GetMessageLink -> Bool
$c/= :: GetMessageLink -> GetMessageLink -> Bool
== :: GetMessageLink -> GetMessageLink -> Bool
$c== :: GetMessageLink -> GetMessageLink -> Bool
Eq, (forall x. GetMessageLink -> Rep GetMessageLink x)
-> (forall x. Rep GetMessageLink x -> GetMessageLink)
-> Generic GetMessageLink
forall x. Rep GetMessageLink x -> GetMessageLink
forall x. GetMessageLink -> Rep GetMessageLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMessageLink x -> GetMessageLink
$cfrom :: forall x. GetMessageLink -> Rep GetMessageLink x
Generic)

-- | Parameter of Function getMessageLinkInfo
data GetMessageLinkInfo
  = -- | Returns information about a public or private message link
    GetMessageLinkInfo
      { -- | The message link in the format "https://t.me/c/...", or "tg://privatepost?...", or "https://t.me/username/...", or "tg://resolve?..."
        GetMessageLinkInfo -> T
url :: T
      }
  deriving (Int -> GetMessageLinkInfo -> ShowS
[GetMessageLinkInfo] -> ShowS
GetMessageLinkInfo -> String
(Int -> GetMessageLinkInfo -> ShowS)
-> (GetMessageLinkInfo -> String)
-> ([GetMessageLinkInfo] -> ShowS)
-> Show GetMessageLinkInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMessageLinkInfo] -> ShowS
$cshowList :: [GetMessageLinkInfo] -> ShowS
show :: GetMessageLinkInfo -> String
$cshow :: GetMessageLinkInfo -> String
showsPrec :: Int -> GetMessageLinkInfo -> ShowS
$cshowsPrec :: Int -> GetMessageLinkInfo -> ShowS
Show, GetMessageLinkInfo -> GetMessageLinkInfo -> Bool
(GetMessageLinkInfo -> GetMessageLinkInfo -> Bool)
-> (GetMessageLinkInfo -> GetMessageLinkInfo -> Bool)
-> Eq GetMessageLinkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMessageLinkInfo -> GetMessageLinkInfo -> Bool
$c/= :: GetMessageLinkInfo -> GetMessageLinkInfo -> Bool
== :: GetMessageLinkInfo -> GetMessageLinkInfo -> Bool
$c== :: GetMessageLinkInfo -> GetMessageLinkInfo -> Bool
Eq, (forall x. GetMessageLinkInfo -> Rep GetMessageLinkInfo x)
-> (forall x. Rep GetMessageLinkInfo x -> GetMessageLinkInfo)
-> Generic GetMessageLinkInfo
forall x. Rep GetMessageLinkInfo x -> GetMessageLinkInfo
forall x. GetMessageLinkInfo -> Rep GetMessageLinkInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMessageLinkInfo x -> GetMessageLinkInfo
$cfrom :: forall x. GetMessageLinkInfo -> Rep GetMessageLinkInfo x
Generic)

-- | Parameter of Function sendMessage
data SendMessage
  = -- | Sends a message. Returns the sent message
    SendMessage
      { -- | Target chat
        SendMessage -> Int
chat_id :: I53,
        -- | Identifier of the message to reply to or 0
        SendMessage -> Int
reply_to_message_id :: I53,
        -- | Options to be used to send the message
        SendMessage -> SendMessageOptions
options :: SendMessageOptions,
        -- | Markup for replying to the message; for bots only
        SendMessage -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | The content of the message to be sent
        SendMessage -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> SendMessage -> ShowS
[SendMessage] -> ShowS
SendMessage -> String
(Int -> SendMessage -> ShowS)
-> (SendMessage -> String)
-> ([SendMessage] -> ShowS)
-> Show SendMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendMessage] -> ShowS
$cshowList :: [SendMessage] -> ShowS
show :: SendMessage -> String
$cshow :: SendMessage -> String
showsPrec :: Int -> SendMessage -> ShowS
$cshowsPrec :: Int -> SendMessage -> ShowS
Show, SendMessage -> SendMessage -> Bool
(SendMessage -> SendMessage -> Bool)
-> (SendMessage -> SendMessage -> Bool) -> Eq SendMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendMessage -> SendMessage -> Bool
$c/= :: SendMessage -> SendMessage -> Bool
== :: SendMessage -> SendMessage -> Bool
$c== :: SendMessage -> SendMessage -> Bool
Eq, (forall x. SendMessage -> Rep SendMessage x)
-> (forall x. Rep SendMessage x -> SendMessage)
-> Generic SendMessage
forall x. Rep SendMessage x -> SendMessage
forall x. SendMessage -> Rep SendMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessage x -> SendMessage
$cfrom :: forall x. SendMessage -> Rep SendMessage x
Generic)

-- | Parameter of Function sendMessageAlbum
data SendMessageAlbum
  = -- | Sends messages grouped together into an album. Currently only photo and video messages can be grouped into an album. Returns sent messages
    SendMessageAlbum
      { -- | Target chat
        SendMessageAlbum -> Int
chat_id :: I53,
        -- | Identifier of a message to reply to or 0
        SendMessageAlbum -> Int
reply_to_message_id :: I53,
        -- | Options to be used to send the messages
        SendMessageAlbum -> SendMessageOptions
options :: SendMessageOptions,
        -- | Contents of messages to be sent
        SendMessageAlbum -> [InputMessageContent]
input_message_contents :: ([]) (InputMessageContent)
      }
  deriving (Int -> SendMessageAlbum -> ShowS
[SendMessageAlbum] -> ShowS
SendMessageAlbum -> String
(Int -> SendMessageAlbum -> ShowS)
-> (SendMessageAlbum -> String)
-> ([SendMessageAlbum] -> ShowS)
-> Show SendMessageAlbum
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendMessageAlbum] -> ShowS
$cshowList :: [SendMessageAlbum] -> ShowS
show :: SendMessageAlbum -> String
$cshow :: SendMessageAlbum -> String
showsPrec :: Int -> SendMessageAlbum -> ShowS
$cshowsPrec :: Int -> SendMessageAlbum -> ShowS
Show, SendMessageAlbum -> SendMessageAlbum -> Bool
(SendMessageAlbum -> SendMessageAlbum -> Bool)
-> (SendMessageAlbum -> SendMessageAlbum -> Bool)
-> Eq SendMessageAlbum
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendMessageAlbum -> SendMessageAlbum -> Bool
$c/= :: SendMessageAlbum -> SendMessageAlbum -> Bool
== :: SendMessageAlbum -> SendMessageAlbum -> Bool
$c== :: SendMessageAlbum -> SendMessageAlbum -> Bool
Eq, (forall x. SendMessageAlbum -> Rep SendMessageAlbum x)
-> (forall x. Rep SendMessageAlbum x -> SendMessageAlbum)
-> Generic SendMessageAlbum
forall x. Rep SendMessageAlbum x -> SendMessageAlbum
forall x. SendMessageAlbum -> Rep SendMessageAlbum x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendMessageAlbum x -> SendMessageAlbum
$cfrom :: forall x. SendMessageAlbum -> Rep SendMessageAlbum x
Generic)

-- | Parameter of Function sendBotStartMessage
data SendBotStartMessage
  = -- | Invites a bot to a chat (if it is not yet a member) and sends it the /start command. Bots can't be invited to a private chat other than the chat with the bot. Bots can't be invited to channels (although they can be added as admins) and secret chats. Returns the sent message
    SendBotStartMessage
      { -- | Identifier of the bot
        SendBotStartMessage -> Int
bot_user_id :: I32,
        -- | Identifier of the target chat
        SendBotStartMessage -> Int
chat_id :: I53,
        -- | A hidden parameter sent to the bot for deep linking purposes (https://core.telegram.org/bots#deep-linking)
        SendBotStartMessage -> T
parameter :: T
      }
  deriving (Int -> SendBotStartMessage -> ShowS
[SendBotStartMessage] -> ShowS
SendBotStartMessage -> String
(Int -> SendBotStartMessage -> ShowS)
-> (SendBotStartMessage -> String)
-> ([SendBotStartMessage] -> ShowS)
-> Show SendBotStartMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendBotStartMessage] -> ShowS
$cshowList :: [SendBotStartMessage] -> ShowS
show :: SendBotStartMessage -> String
$cshow :: SendBotStartMessage -> String
showsPrec :: Int -> SendBotStartMessage -> ShowS
$cshowsPrec :: Int -> SendBotStartMessage -> ShowS
Show, SendBotStartMessage -> SendBotStartMessage -> Bool
(SendBotStartMessage -> SendBotStartMessage -> Bool)
-> (SendBotStartMessage -> SendBotStartMessage -> Bool)
-> Eq SendBotStartMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendBotStartMessage -> SendBotStartMessage -> Bool
$c/= :: SendBotStartMessage -> SendBotStartMessage -> Bool
== :: SendBotStartMessage -> SendBotStartMessage -> Bool
$c== :: SendBotStartMessage -> SendBotStartMessage -> Bool
Eq, (forall x. SendBotStartMessage -> Rep SendBotStartMessage x)
-> (forall x. Rep SendBotStartMessage x -> SendBotStartMessage)
-> Generic SendBotStartMessage
forall x. Rep SendBotStartMessage x -> SendBotStartMessage
forall x. SendBotStartMessage -> Rep SendBotStartMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendBotStartMessage x -> SendBotStartMessage
$cfrom :: forall x. SendBotStartMessage -> Rep SendBotStartMessage x
Generic)

-- | Parameter of Function sendInlineQueryResultMessage
data SendInlineQueryResultMessage
  = -- | Sends the result of an inline query as a message. Returns the sent message. Always clears a chat draft message
    SendInlineQueryResultMessage
      { -- | Target chat
        SendInlineQueryResultMessage -> Int
chat_id :: I53,
        -- | Identifier of a message to reply to or 0
        SendInlineQueryResultMessage -> Int
reply_to_message_id :: I53,
        -- | Options to be used to send the message
        SendInlineQueryResultMessage -> SendMessageOptions
options :: SendMessageOptions,
        -- | Identifier of the inline query
        SendInlineQueryResultMessage -> I64
query_id :: I64,
        -- | Identifier of the inline result
        SendInlineQueryResultMessage -> T
result_id :: T,
        -- | If true, there will be no mention of a bot, via which the message is sent. Can be used only for bots GetOption("animation_search_bot_username"), GetOption("photo_search_bot_username") and GetOption("venue_search_bot_username")
        SendInlineQueryResultMessage -> Bool
hide_via_bot :: Bool
      }
  deriving (Int -> SendInlineQueryResultMessage -> ShowS
[SendInlineQueryResultMessage] -> ShowS
SendInlineQueryResultMessage -> String
(Int -> SendInlineQueryResultMessage -> ShowS)
-> (SendInlineQueryResultMessage -> String)
-> ([SendInlineQueryResultMessage] -> ShowS)
-> Show SendInlineQueryResultMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendInlineQueryResultMessage] -> ShowS
$cshowList :: [SendInlineQueryResultMessage] -> ShowS
show :: SendInlineQueryResultMessage -> String
$cshow :: SendInlineQueryResultMessage -> String
showsPrec :: Int -> SendInlineQueryResultMessage -> ShowS
$cshowsPrec :: Int -> SendInlineQueryResultMessage -> ShowS
Show, SendInlineQueryResultMessage
-> SendInlineQueryResultMessage -> Bool
(SendInlineQueryResultMessage
 -> SendInlineQueryResultMessage -> Bool)
-> (SendInlineQueryResultMessage
    -> SendInlineQueryResultMessage -> Bool)
-> Eq SendInlineQueryResultMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendInlineQueryResultMessage
-> SendInlineQueryResultMessage -> Bool
$c/= :: SendInlineQueryResultMessage
-> SendInlineQueryResultMessage -> Bool
== :: SendInlineQueryResultMessage
-> SendInlineQueryResultMessage -> Bool
$c== :: SendInlineQueryResultMessage
-> SendInlineQueryResultMessage -> Bool
Eq, (forall x.
 SendInlineQueryResultMessage -> Rep SendInlineQueryResultMessage x)
-> (forall x.
    Rep SendInlineQueryResultMessage x -> SendInlineQueryResultMessage)
-> Generic SendInlineQueryResultMessage
forall x.
Rep SendInlineQueryResultMessage x -> SendInlineQueryResultMessage
forall x.
SendInlineQueryResultMessage -> Rep SendInlineQueryResultMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendInlineQueryResultMessage x -> SendInlineQueryResultMessage
$cfrom :: forall x.
SendInlineQueryResultMessage -> Rep SendInlineQueryResultMessage x
Generic)

-- | Parameter of Function forwardMessages
data ForwardMessages
  = -- | Forwards previously sent messages. Returns the forwarded messages in the same order as the message identifiers passed in message_ids. If a message can't be forwarded, null will be returned instead of the message
    ForwardMessages
      { -- | Identifier of the chat to which to forward messages
        ForwardMessages -> Int
chat_id :: I53,
        -- | Identifier of the chat from which to forward messages
        ForwardMessages -> Int
from_chat_id :: I53,
        -- | Identifiers of the messages to forward
        ForwardMessages -> [Int]
message_ids :: ([]) (I53),
        -- | Options to be used to send the messages
        ForwardMessages -> SendMessageOptions
options :: SendMessageOptions,
        -- | True, if the messages should be grouped into an album after forwarding. For this to work, no more than 10 messages may be forwarded, and all of them must be photo or video messages
        ForwardMessages -> Bool
as_album :: Bool,
        -- | True, if content of the messages needs to be copied without links to the original messages. Always true if the messages are forwarded to a secret chat
        ForwardMessages -> Bool
send_copy :: Bool,
        -- | True, if media captions of message copies needs to be removed. Ignored if send_copy is false
        ForwardMessages -> Bool
remove_caption :: Bool
      }
  deriving (Int -> ForwardMessages -> ShowS
[ForwardMessages] -> ShowS
ForwardMessages -> String
(Int -> ForwardMessages -> ShowS)
-> (ForwardMessages -> String)
-> ([ForwardMessages] -> ShowS)
-> Show ForwardMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ForwardMessages] -> ShowS
$cshowList :: [ForwardMessages] -> ShowS
show :: ForwardMessages -> String
$cshow :: ForwardMessages -> String
showsPrec :: Int -> ForwardMessages -> ShowS
$cshowsPrec :: Int -> ForwardMessages -> ShowS
Show, ForwardMessages -> ForwardMessages -> Bool
(ForwardMessages -> ForwardMessages -> Bool)
-> (ForwardMessages -> ForwardMessages -> Bool)
-> Eq ForwardMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ForwardMessages -> ForwardMessages -> Bool
$c/= :: ForwardMessages -> ForwardMessages -> Bool
== :: ForwardMessages -> ForwardMessages -> Bool
$c== :: ForwardMessages -> ForwardMessages -> Bool
Eq, (forall x. ForwardMessages -> Rep ForwardMessages x)
-> (forall x. Rep ForwardMessages x -> ForwardMessages)
-> Generic ForwardMessages
forall x. Rep ForwardMessages x -> ForwardMessages
forall x. ForwardMessages -> Rep ForwardMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ForwardMessages x -> ForwardMessages
$cfrom :: forall x. ForwardMessages -> Rep ForwardMessages x
Generic)

-- | Parameter of Function resendMessages
data ResendMessages
  = -- | Resends messages which failed to send. Can be called only for messages for which messageSendingStateFailed.can_retry is true and after specified in messageSendingStateFailed.retry_after time passed.
    ResendMessages
      { -- | Identifier of the chat to send messages
        ResendMessages -> Int
chat_id :: I53,
        -- | Identifiers of the messages to resend. Message identifiers must be in a strictly increasing order
        ResendMessages -> [Int]
message_ids :: ([]) (I53)
      }
  deriving (Int -> ResendMessages -> ShowS
[ResendMessages] -> ShowS
ResendMessages -> String
(Int -> ResendMessages -> ShowS)
-> (ResendMessages -> String)
-> ([ResendMessages] -> ShowS)
-> Show ResendMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendMessages] -> ShowS
$cshowList :: [ResendMessages] -> ShowS
show :: ResendMessages -> String
$cshow :: ResendMessages -> String
showsPrec :: Int -> ResendMessages -> ShowS
$cshowsPrec :: Int -> ResendMessages -> ShowS
Show, ResendMessages -> ResendMessages -> Bool
(ResendMessages -> ResendMessages -> Bool)
-> (ResendMessages -> ResendMessages -> Bool) -> Eq ResendMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendMessages -> ResendMessages -> Bool
$c/= :: ResendMessages -> ResendMessages -> Bool
== :: ResendMessages -> ResendMessages -> Bool
$c== :: ResendMessages -> ResendMessages -> Bool
Eq, (forall x. ResendMessages -> Rep ResendMessages x)
-> (forall x. Rep ResendMessages x -> ResendMessages)
-> Generic ResendMessages
forall x. Rep ResendMessages x -> ResendMessages
forall x. ResendMessages -> Rep ResendMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResendMessages x -> ResendMessages
$cfrom :: forall x. ResendMessages -> Rep ResendMessages x
Generic)

-- | Parameter of Function sendChatSetTtlMessage
data SendChatSetTtlMessage
  = -- | Changes the current TTL setting (sets a new self-destruct timer) in a secret chat and sends the corresponding message
    SendChatSetTtlMessage
      { -- | Chat identifier
        SendChatSetTtlMessage -> Int
chat_id :: I53,
        -- | New TTL value, in seconds
        SendChatSetTtlMessage -> Int
ttl :: I32
      }
  deriving (Int -> SendChatSetTtlMessage -> ShowS
[SendChatSetTtlMessage] -> ShowS
SendChatSetTtlMessage -> String
(Int -> SendChatSetTtlMessage -> ShowS)
-> (SendChatSetTtlMessage -> String)
-> ([SendChatSetTtlMessage] -> ShowS)
-> Show SendChatSetTtlMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendChatSetTtlMessage] -> ShowS
$cshowList :: [SendChatSetTtlMessage] -> ShowS
show :: SendChatSetTtlMessage -> String
$cshow :: SendChatSetTtlMessage -> String
showsPrec :: Int -> SendChatSetTtlMessage -> ShowS
$cshowsPrec :: Int -> SendChatSetTtlMessage -> ShowS
Show, SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool
(SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool)
-> (SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool)
-> Eq SendChatSetTtlMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool
$c/= :: SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool
== :: SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool
$c== :: SendChatSetTtlMessage -> SendChatSetTtlMessage -> Bool
Eq, (forall x. SendChatSetTtlMessage -> Rep SendChatSetTtlMessage x)
-> (forall x. Rep SendChatSetTtlMessage x -> SendChatSetTtlMessage)
-> Generic SendChatSetTtlMessage
forall x. Rep SendChatSetTtlMessage x -> SendChatSetTtlMessage
forall x. SendChatSetTtlMessage -> Rep SendChatSetTtlMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendChatSetTtlMessage x -> SendChatSetTtlMessage
$cfrom :: forall x. SendChatSetTtlMessage -> Rep SendChatSetTtlMessage x
Generic)

-- | Parameter of Function sendChatScreenshotTakenNotification
data SendChatScreenshotTakenNotification
  = -- | Sends a notification about a screenshot taken in a chat. Supported only in private and secret chats
    SendChatScreenshotTakenNotification
      { -- | Chat identifier
        SendChatScreenshotTakenNotification -> Int
chat_id :: I53
      }
  deriving (Int -> SendChatScreenshotTakenNotification -> ShowS
[SendChatScreenshotTakenNotification] -> ShowS
SendChatScreenshotTakenNotification -> String
(Int -> SendChatScreenshotTakenNotification -> ShowS)
-> (SendChatScreenshotTakenNotification -> String)
-> ([SendChatScreenshotTakenNotification] -> ShowS)
-> Show SendChatScreenshotTakenNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendChatScreenshotTakenNotification] -> ShowS
$cshowList :: [SendChatScreenshotTakenNotification] -> ShowS
show :: SendChatScreenshotTakenNotification -> String
$cshow :: SendChatScreenshotTakenNotification -> String
showsPrec :: Int -> SendChatScreenshotTakenNotification -> ShowS
$cshowsPrec :: Int -> SendChatScreenshotTakenNotification -> ShowS
Show, SendChatScreenshotTakenNotification
-> SendChatScreenshotTakenNotification -> Bool
(SendChatScreenshotTakenNotification
 -> SendChatScreenshotTakenNotification -> Bool)
-> (SendChatScreenshotTakenNotification
    -> SendChatScreenshotTakenNotification -> Bool)
-> Eq SendChatScreenshotTakenNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendChatScreenshotTakenNotification
-> SendChatScreenshotTakenNotification -> Bool
$c/= :: SendChatScreenshotTakenNotification
-> SendChatScreenshotTakenNotification -> Bool
== :: SendChatScreenshotTakenNotification
-> SendChatScreenshotTakenNotification -> Bool
$c== :: SendChatScreenshotTakenNotification
-> SendChatScreenshotTakenNotification -> Bool
Eq, (forall x.
 SendChatScreenshotTakenNotification
 -> Rep SendChatScreenshotTakenNotification x)
-> (forall x.
    Rep SendChatScreenshotTakenNotification x
    -> SendChatScreenshotTakenNotification)
-> Generic SendChatScreenshotTakenNotification
forall x.
Rep SendChatScreenshotTakenNotification x
-> SendChatScreenshotTakenNotification
forall x.
SendChatScreenshotTakenNotification
-> Rep SendChatScreenshotTakenNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendChatScreenshotTakenNotification x
-> SendChatScreenshotTakenNotification
$cfrom :: forall x.
SendChatScreenshotTakenNotification
-> Rep SendChatScreenshotTakenNotification x
Generic)

-- | Parameter of Function addLocalMessage
data AddLocalMessage
  = -- | Adds a local message to a chat. The message is persistent across application restarts only if the message database is used. Returns the added message
    AddLocalMessage
      { -- | Target chat
        AddLocalMessage -> Int
chat_id :: I53,
        -- | Identifier of the user who will be shown as the sender of the message; may be 0 for channel posts
        AddLocalMessage -> Int
sender_user_id :: I32,
        -- | Identifier of the message to reply to or 0
        AddLocalMessage -> Int
reply_to_message_id :: I53,
        -- | Pass true to disable notification for the message
        AddLocalMessage -> Bool
disable_notification :: Bool,
        -- | The content of the message to be added
        AddLocalMessage -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> AddLocalMessage -> ShowS
[AddLocalMessage] -> ShowS
AddLocalMessage -> String
(Int -> AddLocalMessage -> ShowS)
-> (AddLocalMessage -> String)
-> ([AddLocalMessage] -> ShowS)
-> Show AddLocalMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddLocalMessage] -> ShowS
$cshowList :: [AddLocalMessage] -> ShowS
show :: AddLocalMessage -> String
$cshow :: AddLocalMessage -> String
showsPrec :: Int -> AddLocalMessage -> ShowS
$cshowsPrec :: Int -> AddLocalMessage -> ShowS
Show, AddLocalMessage -> AddLocalMessage -> Bool
(AddLocalMessage -> AddLocalMessage -> Bool)
-> (AddLocalMessage -> AddLocalMessage -> Bool)
-> Eq AddLocalMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddLocalMessage -> AddLocalMessage -> Bool
$c/= :: AddLocalMessage -> AddLocalMessage -> Bool
== :: AddLocalMessage -> AddLocalMessage -> Bool
$c== :: AddLocalMessage -> AddLocalMessage -> Bool
Eq, (forall x. AddLocalMessage -> Rep AddLocalMessage x)
-> (forall x. Rep AddLocalMessage x -> AddLocalMessage)
-> Generic AddLocalMessage
forall x. Rep AddLocalMessage x -> AddLocalMessage
forall x. AddLocalMessage -> Rep AddLocalMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddLocalMessage x -> AddLocalMessage
$cfrom :: forall x. AddLocalMessage -> Rep AddLocalMessage x
Generic)

-- | Parameter of Function deleteMessages
data DeleteMessages
  = -- | Deletes messages
    DeleteMessages
      { -- | Chat identifier
        DeleteMessages -> Int
chat_id :: I53,
        -- | Identifiers of the messages to be deleted
        DeleteMessages -> [Int]
message_ids :: ([]) (I53),
        -- | Pass true to try to delete messages for all chat members. Always true for supergroups, channels and secret chats
        DeleteMessages -> Bool
revoke :: Bool
      }
  deriving (Int -> DeleteMessages -> ShowS
[DeleteMessages] -> ShowS
DeleteMessages -> String
(Int -> DeleteMessages -> ShowS)
-> (DeleteMessages -> String)
-> ([DeleteMessages] -> ShowS)
-> Show DeleteMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteMessages] -> ShowS
$cshowList :: [DeleteMessages] -> ShowS
show :: DeleteMessages -> String
$cshow :: DeleteMessages -> String
showsPrec :: Int -> DeleteMessages -> ShowS
$cshowsPrec :: Int -> DeleteMessages -> ShowS
Show, DeleteMessages -> DeleteMessages -> Bool
(DeleteMessages -> DeleteMessages -> Bool)
-> (DeleteMessages -> DeleteMessages -> Bool) -> Eq DeleteMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteMessages -> DeleteMessages -> Bool
$c/= :: DeleteMessages -> DeleteMessages -> Bool
== :: DeleteMessages -> DeleteMessages -> Bool
$c== :: DeleteMessages -> DeleteMessages -> Bool
Eq, (forall x. DeleteMessages -> Rep DeleteMessages x)
-> (forall x. Rep DeleteMessages x -> DeleteMessages)
-> Generic DeleteMessages
forall x. Rep DeleteMessages x -> DeleteMessages
forall x. DeleteMessages -> Rep DeleteMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteMessages x -> DeleteMessages
$cfrom :: forall x. DeleteMessages -> Rep DeleteMessages x
Generic)

-- | Parameter of Function deleteChatMessagesFromUser
data DeleteChatMessagesFromUser
  = -- | Deletes all messages sent by the specified user to a chat. Supported only for supergroups; requires can_delete_messages administrator privileges
    DeleteChatMessagesFromUser
      { -- | Chat identifier
        DeleteChatMessagesFromUser -> Int
chat_id :: I53,
        -- | User identifier
        DeleteChatMessagesFromUser -> Int
user_id :: I32
      }
  deriving (Int -> DeleteChatMessagesFromUser -> ShowS
[DeleteChatMessagesFromUser] -> ShowS
DeleteChatMessagesFromUser -> String
(Int -> DeleteChatMessagesFromUser -> ShowS)
-> (DeleteChatMessagesFromUser -> String)
-> ([DeleteChatMessagesFromUser] -> ShowS)
-> Show DeleteChatMessagesFromUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteChatMessagesFromUser] -> ShowS
$cshowList :: [DeleteChatMessagesFromUser] -> ShowS
show :: DeleteChatMessagesFromUser -> String
$cshow :: DeleteChatMessagesFromUser -> String
showsPrec :: Int -> DeleteChatMessagesFromUser -> ShowS
$cshowsPrec :: Int -> DeleteChatMessagesFromUser -> ShowS
Show, DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool
(DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool)
-> (DeleteChatMessagesFromUser
    -> DeleteChatMessagesFromUser -> Bool)
-> Eq DeleteChatMessagesFromUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool
$c/= :: DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool
== :: DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool
$c== :: DeleteChatMessagesFromUser -> DeleteChatMessagesFromUser -> Bool
Eq, (forall x.
 DeleteChatMessagesFromUser -> Rep DeleteChatMessagesFromUser x)
-> (forall x.
    Rep DeleteChatMessagesFromUser x -> DeleteChatMessagesFromUser)
-> Generic DeleteChatMessagesFromUser
forall x.
Rep DeleteChatMessagesFromUser x -> DeleteChatMessagesFromUser
forall x.
DeleteChatMessagesFromUser -> Rep DeleteChatMessagesFromUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteChatMessagesFromUser x -> DeleteChatMessagesFromUser
$cfrom :: forall x.
DeleteChatMessagesFromUser -> Rep DeleteChatMessagesFromUser x
Generic)

-- | Parameter of Function editMessageText
data EditMessageText
  = -- | Edits the text of a message (or a text of a game message). Returns the edited message after the edit is completed on the server side
    EditMessageText
      { -- | The chat the message belongs to
        EditMessageText -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageText -> Int
message_id :: I53,
        -- | The new message reply markup; for bots only
        EditMessageText -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New text content of the message. Should be of type InputMessageText
        EditMessageText -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> EditMessageText -> ShowS
[EditMessageText] -> ShowS
EditMessageText -> String
(Int -> EditMessageText -> ShowS)
-> (EditMessageText -> String)
-> ([EditMessageText] -> ShowS)
-> Show EditMessageText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageText] -> ShowS
$cshowList :: [EditMessageText] -> ShowS
show :: EditMessageText -> String
$cshow :: EditMessageText -> String
showsPrec :: Int -> EditMessageText -> ShowS
$cshowsPrec :: Int -> EditMessageText -> ShowS
Show, EditMessageText -> EditMessageText -> Bool
(EditMessageText -> EditMessageText -> Bool)
-> (EditMessageText -> EditMessageText -> Bool)
-> Eq EditMessageText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageText -> EditMessageText -> Bool
$c/= :: EditMessageText -> EditMessageText -> Bool
== :: EditMessageText -> EditMessageText -> Bool
$c== :: EditMessageText -> EditMessageText -> Bool
Eq, (forall x. EditMessageText -> Rep EditMessageText x)
-> (forall x. Rep EditMessageText x -> EditMessageText)
-> Generic EditMessageText
forall x. Rep EditMessageText x -> EditMessageText
forall x. EditMessageText -> Rep EditMessageText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditMessageText x -> EditMessageText
$cfrom :: forall x. EditMessageText -> Rep EditMessageText x
Generic)

-- | Parameter of Function editMessageLiveLocation
data EditMessageLiveLocation
  = -- | Edits the message content of a live location. Messages can be edited for a limited period of time specified in the live location. Returns the edited message after the edit is completed on the server side
    EditMessageLiveLocation
      { -- | The chat the message belongs to
        EditMessageLiveLocation -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageLiveLocation -> Int
message_id :: I53,
        -- | The new message reply markup; for bots only
        EditMessageLiveLocation -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New location content of the message; may be null. Pass null to stop sharing the live location
        EditMessageLiveLocation -> Location
location :: Location
      }
  deriving (Int -> EditMessageLiveLocation -> ShowS
[EditMessageLiveLocation] -> ShowS
EditMessageLiveLocation -> String
(Int -> EditMessageLiveLocation -> ShowS)
-> (EditMessageLiveLocation -> String)
-> ([EditMessageLiveLocation] -> ShowS)
-> Show EditMessageLiveLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageLiveLocation] -> ShowS
$cshowList :: [EditMessageLiveLocation] -> ShowS
show :: EditMessageLiveLocation -> String
$cshow :: EditMessageLiveLocation -> String
showsPrec :: Int -> EditMessageLiveLocation -> ShowS
$cshowsPrec :: Int -> EditMessageLiveLocation -> ShowS
Show, EditMessageLiveLocation -> EditMessageLiveLocation -> Bool
(EditMessageLiveLocation -> EditMessageLiveLocation -> Bool)
-> (EditMessageLiveLocation -> EditMessageLiveLocation -> Bool)
-> Eq EditMessageLiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageLiveLocation -> EditMessageLiveLocation -> Bool
$c/= :: EditMessageLiveLocation -> EditMessageLiveLocation -> Bool
== :: EditMessageLiveLocation -> EditMessageLiveLocation -> Bool
$c== :: EditMessageLiveLocation -> EditMessageLiveLocation -> Bool
Eq, (forall x.
 EditMessageLiveLocation -> Rep EditMessageLiveLocation x)
-> (forall x.
    Rep EditMessageLiveLocation x -> EditMessageLiveLocation)
-> Generic EditMessageLiveLocation
forall x. Rep EditMessageLiveLocation x -> EditMessageLiveLocation
forall x. EditMessageLiveLocation -> Rep EditMessageLiveLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditMessageLiveLocation x -> EditMessageLiveLocation
$cfrom :: forall x. EditMessageLiveLocation -> Rep EditMessageLiveLocation x
Generic)

-- | Parameter of Function editMessageMedia
data EditMessageMedia
  = -- | Edits the content of a message with an animation, an audio, a document, a photo or a video. The media in the message can't be replaced if the message was set to self-destruct. Media can't be replaced by self-destructing media. Media in an album can be edited only to contain a photo or a video. Returns the edited message after the edit is completed on the server side
    EditMessageMedia
      { -- | The chat the message belongs to
        EditMessageMedia -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageMedia -> Int
message_id :: I53,
        -- | The new message reply markup; for bots only
        EditMessageMedia -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New content of the message. Must be one of the following types: InputMessageAnimation, InputMessageAudio, InputMessageDocument, InputMessagePhoto or InputMessageVideo
        EditMessageMedia -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> EditMessageMedia -> ShowS
[EditMessageMedia] -> ShowS
EditMessageMedia -> String
(Int -> EditMessageMedia -> ShowS)
-> (EditMessageMedia -> String)
-> ([EditMessageMedia] -> ShowS)
-> Show EditMessageMedia
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageMedia] -> ShowS
$cshowList :: [EditMessageMedia] -> ShowS
show :: EditMessageMedia -> String
$cshow :: EditMessageMedia -> String
showsPrec :: Int -> EditMessageMedia -> ShowS
$cshowsPrec :: Int -> EditMessageMedia -> ShowS
Show, EditMessageMedia -> EditMessageMedia -> Bool
(EditMessageMedia -> EditMessageMedia -> Bool)
-> (EditMessageMedia -> EditMessageMedia -> Bool)
-> Eq EditMessageMedia
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageMedia -> EditMessageMedia -> Bool
$c/= :: EditMessageMedia -> EditMessageMedia -> Bool
== :: EditMessageMedia -> EditMessageMedia -> Bool
$c== :: EditMessageMedia -> EditMessageMedia -> Bool
Eq, (forall x. EditMessageMedia -> Rep EditMessageMedia x)
-> (forall x. Rep EditMessageMedia x -> EditMessageMedia)
-> Generic EditMessageMedia
forall x. Rep EditMessageMedia x -> EditMessageMedia
forall x. EditMessageMedia -> Rep EditMessageMedia x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditMessageMedia x -> EditMessageMedia
$cfrom :: forall x. EditMessageMedia -> Rep EditMessageMedia x
Generic)

-- | Parameter of Function editMessageCaption
data EditMessageCaption
  = -- | Edits the message content caption. Returns the edited message after the edit is completed on the server side
    EditMessageCaption
      { -- | The chat the message belongs to
        EditMessageCaption -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageCaption -> Int
message_id :: I53,
        -- | The new message reply markup; for bots only
        EditMessageCaption -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New message content caption; 0-GetOption("message_caption_length_max") characters
        EditMessageCaption -> FormattedText
caption :: FormattedText
      }
  deriving (Int -> EditMessageCaption -> ShowS
[EditMessageCaption] -> ShowS
EditMessageCaption -> String
(Int -> EditMessageCaption -> ShowS)
-> (EditMessageCaption -> String)
-> ([EditMessageCaption] -> ShowS)
-> Show EditMessageCaption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageCaption] -> ShowS
$cshowList :: [EditMessageCaption] -> ShowS
show :: EditMessageCaption -> String
$cshow :: EditMessageCaption -> String
showsPrec :: Int -> EditMessageCaption -> ShowS
$cshowsPrec :: Int -> EditMessageCaption -> ShowS
Show, EditMessageCaption -> EditMessageCaption -> Bool
(EditMessageCaption -> EditMessageCaption -> Bool)
-> (EditMessageCaption -> EditMessageCaption -> Bool)
-> Eq EditMessageCaption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageCaption -> EditMessageCaption -> Bool
$c/= :: EditMessageCaption -> EditMessageCaption -> Bool
== :: EditMessageCaption -> EditMessageCaption -> Bool
$c== :: EditMessageCaption -> EditMessageCaption -> Bool
Eq, (forall x. EditMessageCaption -> Rep EditMessageCaption x)
-> (forall x. Rep EditMessageCaption x -> EditMessageCaption)
-> Generic EditMessageCaption
forall x. Rep EditMessageCaption x -> EditMessageCaption
forall x. EditMessageCaption -> Rep EditMessageCaption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditMessageCaption x -> EditMessageCaption
$cfrom :: forall x. EditMessageCaption -> Rep EditMessageCaption x
Generic)

-- | Parameter of Function editMessageReplyMarkup
data EditMessageReplyMarkup
  = -- | Edits the message reply markup; for bots only. Returns the edited message after the edit is completed on the server side
    EditMessageReplyMarkup
      { -- | The chat the message belongs to
        EditMessageReplyMarkup -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageReplyMarkup -> Int
message_id :: I53,
        -- | The new message reply markup
        EditMessageReplyMarkup -> ReplyMarkup
reply_markup :: ReplyMarkup
      }
  deriving (Int -> EditMessageReplyMarkup -> ShowS
[EditMessageReplyMarkup] -> ShowS
EditMessageReplyMarkup -> String
(Int -> EditMessageReplyMarkup -> ShowS)
-> (EditMessageReplyMarkup -> String)
-> ([EditMessageReplyMarkup] -> ShowS)
-> Show EditMessageReplyMarkup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageReplyMarkup] -> ShowS
$cshowList :: [EditMessageReplyMarkup] -> ShowS
show :: EditMessageReplyMarkup -> String
$cshow :: EditMessageReplyMarkup -> String
showsPrec :: Int -> EditMessageReplyMarkup -> ShowS
$cshowsPrec :: Int -> EditMessageReplyMarkup -> ShowS
Show, EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool
(EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool)
-> (EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool)
-> Eq EditMessageReplyMarkup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool
$c/= :: EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool
== :: EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool
$c== :: EditMessageReplyMarkup -> EditMessageReplyMarkup -> Bool
Eq, (forall x. EditMessageReplyMarkup -> Rep EditMessageReplyMarkup x)
-> (forall x.
    Rep EditMessageReplyMarkup x -> EditMessageReplyMarkup)
-> Generic EditMessageReplyMarkup
forall x. Rep EditMessageReplyMarkup x -> EditMessageReplyMarkup
forall x. EditMessageReplyMarkup -> Rep EditMessageReplyMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditMessageReplyMarkup x -> EditMessageReplyMarkup
$cfrom :: forall x. EditMessageReplyMarkup -> Rep EditMessageReplyMarkup x
Generic)

-- | Parameter of Function editInlineMessageText
data EditInlineMessageText
  = -- | Edits the text of an inline text or game message sent via a bot; for bots only
    EditInlineMessageText
      { -- | Inline message identifier
        EditInlineMessageText -> T
inline_message_id :: T,
        -- | The new message reply markup
        EditInlineMessageText -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New text content of the message. Should be of type InputMessageText
        EditInlineMessageText -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> EditInlineMessageText -> ShowS
[EditInlineMessageText] -> ShowS
EditInlineMessageText -> String
(Int -> EditInlineMessageText -> ShowS)
-> (EditInlineMessageText -> String)
-> ([EditInlineMessageText] -> ShowS)
-> Show EditInlineMessageText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditInlineMessageText] -> ShowS
$cshowList :: [EditInlineMessageText] -> ShowS
show :: EditInlineMessageText -> String
$cshow :: EditInlineMessageText -> String
showsPrec :: Int -> EditInlineMessageText -> ShowS
$cshowsPrec :: Int -> EditInlineMessageText -> ShowS
Show, EditInlineMessageText -> EditInlineMessageText -> Bool
(EditInlineMessageText -> EditInlineMessageText -> Bool)
-> (EditInlineMessageText -> EditInlineMessageText -> Bool)
-> Eq EditInlineMessageText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditInlineMessageText -> EditInlineMessageText -> Bool
$c/= :: EditInlineMessageText -> EditInlineMessageText -> Bool
== :: EditInlineMessageText -> EditInlineMessageText -> Bool
$c== :: EditInlineMessageText -> EditInlineMessageText -> Bool
Eq, (forall x. EditInlineMessageText -> Rep EditInlineMessageText x)
-> (forall x. Rep EditInlineMessageText x -> EditInlineMessageText)
-> Generic EditInlineMessageText
forall x. Rep EditInlineMessageText x -> EditInlineMessageText
forall x. EditInlineMessageText -> Rep EditInlineMessageText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditInlineMessageText x -> EditInlineMessageText
$cfrom :: forall x. EditInlineMessageText -> Rep EditInlineMessageText x
Generic)

-- | Parameter of Function editInlineMessageLiveLocation
data EditInlineMessageLiveLocation
  = -- | Edits the content of a live location in an inline message sent via a bot; for bots only
    EditInlineMessageLiveLocation
      { -- | Inline message identifier
        EditInlineMessageLiveLocation -> T
inline_message_id :: T,
        -- | The new message reply markup
        EditInlineMessageLiveLocation -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New location content of the message; may be null. Pass null to stop sharing the live location
        EditInlineMessageLiveLocation -> Location
location :: Location
      }
  deriving (Int -> EditInlineMessageLiveLocation -> ShowS
[EditInlineMessageLiveLocation] -> ShowS
EditInlineMessageLiveLocation -> String
(Int -> EditInlineMessageLiveLocation -> ShowS)
-> (EditInlineMessageLiveLocation -> String)
-> ([EditInlineMessageLiveLocation] -> ShowS)
-> Show EditInlineMessageLiveLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditInlineMessageLiveLocation] -> ShowS
$cshowList :: [EditInlineMessageLiveLocation] -> ShowS
show :: EditInlineMessageLiveLocation -> String
$cshow :: EditInlineMessageLiveLocation -> String
showsPrec :: Int -> EditInlineMessageLiveLocation -> ShowS
$cshowsPrec :: Int -> EditInlineMessageLiveLocation -> ShowS
Show, EditInlineMessageLiveLocation
-> EditInlineMessageLiveLocation -> Bool
(EditInlineMessageLiveLocation
 -> EditInlineMessageLiveLocation -> Bool)
-> (EditInlineMessageLiveLocation
    -> EditInlineMessageLiveLocation -> Bool)
-> Eq EditInlineMessageLiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditInlineMessageLiveLocation
-> EditInlineMessageLiveLocation -> Bool
$c/= :: EditInlineMessageLiveLocation
-> EditInlineMessageLiveLocation -> Bool
== :: EditInlineMessageLiveLocation
-> EditInlineMessageLiveLocation -> Bool
$c== :: EditInlineMessageLiveLocation
-> EditInlineMessageLiveLocation -> Bool
Eq, (forall x.
 EditInlineMessageLiveLocation
 -> Rep EditInlineMessageLiveLocation x)
-> (forall x.
    Rep EditInlineMessageLiveLocation x
    -> EditInlineMessageLiveLocation)
-> Generic EditInlineMessageLiveLocation
forall x.
Rep EditInlineMessageLiveLocation x
-> EditInlineMessageLiveLocation
forall x.
EditInlineMessageLiveLocation
-> Rep EditInlineMessageLiveLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditInlineMessageLiveLocation x
-> EditInlineMessageLiveLocation
$cfrom :: forall x.
EditInlineMessageLiveLocation
-> Rep EditInlineMessageLiveLocation x
Generic)

-- | Parameter of Function editInlineMessageMedia
data EditInlineMessageMedia
  = -- | Edits the content of a message with an animation, an audio, a document, a photo or a video in an inline message sent via a bot; for bots only
    EditInlineMessageMedia
      { -- | Inline message identifier
        EditInlineMessageMedia -> T
inline_message_id :: T,
        -- | The new message reply markup; for bots only
        EditInlineMessageMedia -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New content of the message. Must be one of the following types: InputMessageAnimation, InputMessageAudio, InputMessageDocument, InputMessagePhoto or InputMessageVideo
        EditInlineMessageMedia -> InputMessageContent
input_message_content :: InputMessageContent
      }
  deriving (Int -> EditInlineMessageMedia -> ShowS
[EditInlineMessageMedia] -> ShowS
EditInlineMessageMedia -> String
(Int -> EditInlineMessageMedia -> ShowS)
-> (EditInlineMessageMedia -> String)
-> ([EditInlineMessageMedia] -> ShowS)
-> Show EditInlineMessageMedia
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditInlineMessageMedia] -> ShowS
$cshowList :: [EditInlineMessageMedia] -> ShowS
show :: EditInlineMessageMedia -> String
$cshow :: EditInlineMessageMedia -> String
showsPrec :: Int -> EditInlineMessageMedia -> ShowS
$cshowsPrec :: Int -> EditInlineMessageMedia -> ShowS
Show, EditInlineMessageMedia -> EditInlineMessageMedia -> Bool
(EditInlineMessageMedia -> EditInlineMessageMedia -> Bool)
-> (EditInlineMessageMedia -> EditInlineMessageMedia -> Bool)
-> Eq EditInlineMessageMedia
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditInlineMessageMedia -> EditInlineMessageMedia -> Bool
$c/= :: EditInlineMessageMedia -> EditInlineMessageMedia -> Bool
== :: EditInlineMessageMedia -> EditInlineMessageMedia -> Bool
$c== :: EditInlineMessageMedia -> EditInlineMessageMedia -> Bool
Eq, (forall x. EditInlineMessageMedia -> Rep EditInlineMessageMedia x)
-> (forall x.
    Rep EditInlineMessageMedia x -> EditInlineMessageMedia)
-> Generic EditInlineMessageMedia
forall x. Rep EditInlineMessageMedia x -> EditInlineMessageMedia
forall x. EditInlineMessageMedia -> Rep EditInlineMessageMedia x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditInlineMessageMedia x -> EditInlineMessageMedia
$cfrom :: forall x. EditInlineMessageMedia -> Rep EditInlineMessageMedia x
Generic)

-- | Parameter of Function editInlineMessageCaption
data EditInlineMessageCaption
  = -- | Edits the caption of an inline message sent via a bot; for bots only
    EditInlineMessageCaption
      { -- | Inline message identifier
        EditInlineMessageCaption -> T
inline_message_id :: T,
        -- | The new message reply markup
        EditInlineMessageCaption -> ReplyMarkup
reply_markup :: ReplyMarkup,
        -- | New message content caption; 0-GetOption("message_caption_length_max") characters
        EditInlineMessageCaption -> FormattedText
caption :: FormattedText
      }
  deriving (Int -> EditInlineMessageCaption -> ShowS
[EditInlineMessageCaption] -> ShowS
EditInlineMessageCaption -> String
(Int -> EditInlineMessageCaption -> ShowS)
-> (EditInlineMessageCaption -> String)
-> ([EditInlineMessageCaption] -> ShowS)
-> Show EditInlineMessageCaption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditInlineMessageCaption] -> ShowS
$cshowList :: [EditInlineMessageCaption] -> ShowS
show :: EditInlineMessageCaption -> String
$cshow :: EditInlineMessageCaption -> String
showsPrec :: Int -> EditInlineMessageCaption -> ShowS
$cshowsPrec :: Int -> EditInlineMessageCaption -> ShowS
Show, EditInlineMessageCaption -> EditInlineMessageCaption -> Bool
(EditInlineMessageCaption -> EditInlineMessageCaption -> Bool)
-> (EditInlineMessageCaption -> EditInlineMessageCaption -> Bool)
-> Eq EditInlineMessageCaption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditInlineMessageCaption -> EditInlineMessageCaption -> Bool
$c/= :: EditInlineMessageCaption -> EditInlineMessageCaption -> Bool
== :: EditInlineMessageCaption -> EditInlineMessageCaption -> Bool
$c== :: EditInlineMessageCaption -> EditInlineMessageCaption -> Bool
Eq, (forall x.
 EditInlineMessageCaption -> Rep EditInlineMessageCaption x)
-> (forall x.
    Rep EditInlineMessageCaption x -> EditInlineMessageCaption)
-> Generic EditInlineMessageCaption
forall x.
Rep EditInlineMessageCaption x -> EditInlineMessageCaption
forall x.
EditInlineMessageCaption -> Rep EditInlineMessageCaption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditInlineMessageCaption x -> EditInlineMessageCaption
$cfrom :: forall x.
EditInlineMessageCaption -> Rep EditInlineMessageCaption x
Generic)

-- | Parameter of Function editInlineMessageReplyMarkup
data EditInlineMessageReplyMarkup
  = -- | Edits the reply markup of an inline message sent via a bot; for bots only
    EditInlineMessageReplyMarkup
      { -- | Inline message identifier
        EditInlineMessageReplyMarkup -> T
inline_message_id :: T,
        -- | The new message reply markup
        EditInlineMessageReplyMarkup -> ReplyMarkup
reply_markup :: ReplyMarkup
      }
  deriving (Int -> EditInlineMessageReplyMarkup -> ShowS
[EditInlineMessageReplyMarkup] -> ShowS
EditInlineMessageReplyMarkup -> String
(Int -> EditInlineMessageReplyMarkup -> ShowS)
-> (EditInlineMessageReplyMarkup -> String)
-> ([EditInlineMessageReplyMarkup] -> ShowS)
-> Show EditInlineMessageReplyMarkup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditInlineMessageReplyMarkup] -> ShowS
$cshowList :: [EditInlineMessageReplyMarkup] -> ShowS
show :: EditInlineMessageReplyMarkup -> String
$cshow :: EditInlineMessageReplyMarkup -> String
showsPrec :: Int -> EditInlineMessageReplyMarkup -> ShowS
$cshowsPrec :: Int -> EditInlineMessageReplyMarkup -> ShowS
Show, EditInlineMessageReplyMarkup
-> EditInlineMessageReplyMarkup -> Bool
(EditInlineMessageReplyMarkup
 -> EditInlineMessageReplyMarkup -> Bool)
-> (EditInlineMessageReplyMarkup
    -> EditInlineMessageReplyMarkup -> Bool)
-> Eq EditInlineMessageReplyMarkup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditInlineMessageReplyMarkup
-> EditInlineMessageReplyMarkup -> Bool
$c/= :: EditInlineMessageReplyMarkup
-> EditInlineMessageReplyMarkup -> Bool
== :: EditInlineMessageReplyMarkup
-> EditInlineMessageReplyMarkup -> Bool
$c== :: EditInlineMessageReplyMarkup
-> EditInlineMessageReplyMarkup -> Bool
Eq, (forall x.
 EditInlineMessageReplyMarkup -> Rep EditInlineMessageReplyMarkup x)
-> (forall x.
    Rep EditInlineMessageReplyMarkup x -> EditInlineMessageReplyMarkup)
-> Generic EditInlineMessageReplyMarkup
forall x.
Rep EditInlineMessageReplyMarkup x -> EditInlineMessageReplyMarkup
forall x.
EditInlineMessageReplyMarkup -> Rep EditInlineMessageReplyMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditInlineMessageReplyMarkup x -> EditInlineMessageReplyMarkup
$cfrom :: forall x.
EditInlineMessageReplyMarkup -> Rep EditInlineMessageReplyMarkup x
Generic)

-- | Parameter of Function editMessageSchedulingState
data EditMessageSchedulingState
  = -- | Edits the time when a scheduled message will be sent. Scheduling state of all messages in the same album or forwarded together with the message will be also changed
    EditMessageSchedulingState
      { -- | The chat the message belongs to
        EditMessageSchedulingState -> Int
chat_id :: I53,
        -- | Identifier of the message
        EditMessageSchedulingState -> Int
message_id :: I53,
        -- | The new message scheduling state. Pass null to send the message immediately
        EditMessageSchedulingState -> MessageSchedulingState
scheduling_state :: MessageSchedulingState
      }
  deriving (Int -> EditMessageSchedulingState -> ShowS
[EditMessageSchedulingState] -> ShowS
EditMessageSchedulingState -> String
(Int -> EditMessageSchedulingState -> ShowS)
-> (EditMessageSchedulingState -> String)
-> ([EditMessageSchedulingState] -> ShowS)
-> Show EditMessageSchedulingState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditMessageSchedulingState] -> ShowS
$cshowList :: [EditMessageSchedulingState] -> ShowS
show :: EditMessageSchedulingState -> String
$cshow :: EditMessageSchedulingState -> String
showsPrec :: Int -> EditMessageSchedulingState -> ShowS
$cshowsPrec :: Int -> EditMessageSchedulingState -> ShowS
Show, EditMessageSchedulingState -> EditMessageSchedulingState -> Bool
(EditMessageSchedulingState -> EditMessageSchedulingState -> Bool)
-> (EditMessageSchedulingState
    -> EditMessageSchedulingState -> Bool)
-> Eq EditMessageSchedulingState
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditMessageSchedulingState -> EditMessageSchedulingState -> Bool
$c/= :: EditMessageSchedulingState -> EditMessageSchedulingState -> Bool
== :: EditMessageSchedulingState -> EditMessageSchedulingState -> Bool
$c== :: EditMessageSchedulingState -> EditMessageSchedulingState -> Bool
Eq, (forall x.
 EditMessageSchedulingState -> Rep EditMessageSchedulingState x)
-> (forall x.
    Rep EditMessageSchedulingState x -> EditMessageSchedulingState)
-> Generic EditMessageSchedulingState
forall x.
Rep EditMessageSchedulingState x -> EditMessageSchedulingState
forall x.
EditMessageSchedulingState -> Rep EditMessageSchedulingState x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditMessageSchedulingState x -> EditMessageSchedulingState
$cfrom :: forall x.
EditMessageSchedulingState -> Rep EditMessageSchedulingState x
Generic)

-- | Parameter of Function getTextEntities
data GetTextEntities
  = -- | Returns all entities (mentions, hashtags, cashtags, bot commands, bank card numbers, URLs, and email addresses) contained in the text. This is an offline method. Can be called before authorization. Can be called synchronously
    GetTextEntities
      { -- | The text in which to look for entites
        GetTextEntities -> T
text :: T
      }
  deriving (Int -> GetTextEntities -> ShowS
[GetTextEntities] -> ShowS
GetTextEntities -> String
(Int -> GetTextEntities -> ShowS)
-> (GetTextEntities -> String)
-> ([GetTextEntities] -> ShowS)
-> Show GetTextEntities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTextEntities] -> ShowS
$cshowList :: [GetTextEntities] -> ShowS
show :: GetTextEntities -> String
$cshow :: GetTextEntities -> String
showsPrec :: Int -> GetTextEntities -> ShowS
$cshowsPrec :: Int -> GetTextEntities -> ShowS
Show, GetTextEntities -> GetTextEntities -> Bool
(GetTextEntities -> GetTextEntities -> Bool)
-> (GetTextEntities -> GetTextEntities -> Bool)
-> Eq GetTextEntities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTextEntities -> GetTextEntities -> Bool
$c/= :: GetTextEntities -> GetTextEntities -> Bool
== :: GetTextEntities -> GetTextEntities -> Bool
$c== :: GetTextEntities -> GetTextEntities -> Bool
Eq, (forall x. GetTextEntities -> Rep GetTextEntities x)
-> (forall x. Rep GetTextEntities x -> GetTextEntities)
-> Generic GetTextEntities
forall x. Rep GetTextEntities x -> GetTextEntities
forall x. GetTextEntities -> Rep GetTextEntities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTextEntities x -> GetTextEntities
$cfrom :: forall x. GetTextEntities -> Rep GetTextEntities x
Generic)

-- | Parameter of Function parseTextEntities
data ParseTextEntities
  = -- | Parses Bold, Italic, Underline, Strikethrough, Code, Pre, PreCode, TextUrl and MentionName entities contained in the text. This is an offline method. Can be called before authorization. Can be called synchronously
    ParseTextEntities
      { -- | The text to parse
        ParseTextEntities -> T
text :: T,
        -- | Text parse mode
        ParseTextEntities -> TextParseMode
parse_mode :: TextParseMode
      }
  deriving (Int -> ParseTextEntities -> ShowS
[ParseTextEntities] -> ShowS
ParseTextEntities -> String
(Int -> ParseTextEntities -> ShowS)
-> (ParseTextEntities -> String)
-> ([ParseTextEntities] -> ShowS)
-> Show ParseTextEntities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseTextEntities] -> ShowS
$cshowList :: [ParseTextEntities] -> ShowS
show :: ParseTextEntities -> String
$cshow :: ParseTextEntities -> String
showsPrec :: Int -> ParseTextEntities -> ShowS
$cshowsPrec :: Int -> ParseTextEntities -> ShowS
Show, ParseTextEntities -> ParseTextEntities -> Bool
(ParseTextEntities -> ParseTextEntities -> Bool)
-> (ParseTextEntities -> ParseTextEntities -> Bool)
-> Eq ParseTextEntities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseTextEntities -> ParseTextEntities -> Bool
$c/= :: ParseTextEntities -> ParseTextEntities -> Bool
== :: ParseTextEntities -> ParseTextEntities -> Bool
$c== :: ParseTextEntities -> ParseTextEntities -> Bool
Eq, (forall x. ParseTextEntities -> Rep ParseTextEntities x)
-> (forall x. Rep ParseTextEntities x -> ParseTextEntities)
-> Generic ParseTextEntities
forall x. Rep ParseTextEntities x -> ParseTextEntities
forall x. ParseTextEntities -> Rep ParseTextEntities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParseTextEntities x -> ParseTextEntities
$cfrom :: forall x. ParseTextEntities -> Rep ParseTextEntities x
Generic)

-- | Parameter of Function parseMarkdown
data ParseMarkdown
  = -- | Parses Markdown entities in a human-friendly format, ignoring mark up errors. This is an offline method. Can be called before authorization. Can be called synchronously
    ParseMarkdown
      { -- | The text to parse. For example, "__italic__ ~~strikethrough~~ **bold** `code` ```pre``` __[italic__ text_url](telegram.org) __italic**bold italic__bold**"
        ParseMarkdown -> FormattedText
text :: FormattedText
      }
  deriving (Int -> ParseMarkdown -> ShowS
[ParseMarkdown] -> ShowS
ParseMarkdown -> String
(Int -> ParseMarkdown -> ShowS)
-> (ParseMarkdown -> String)
-> ([ParseMarkdown] -> ShowS)
-> Show ParseMarkdown
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseMarkdown] -> ShowS
$cshowList :: [ParseMarkdown] -> ShowS
show :: ParseMarkdown -> String
$cshow :: ParseMarkdown -> String
showsPrec :: Int -> ParseMarkdown -> ShowS
$cshowsPrec :: Int -> ParseMarkdown -> ShowS
Show, ParseMarkdown -> ParseMarkdown -> Bool
(ParseMarkdown -> ParseMarkdown -> Bool)
-> (ParseMarkdown -> ParseMarkdown -> Bool) -> Eq ParseMarkdown
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ParseMarkdown -> ParseMarkdown -> Bool
$c/= :: ParseMarkdown -> ParseMarkdown -> Bool
== :: ParseMarkdown -> ParseMarkdown -> Bool
$c== :: ParseMarkdown -> ParseMarkdown -> Bool
Eq, (forall x. ParseMarkdown -> Rep ParseMarkdown x)
-> (forall x. Rep ParseMarkdown x -> ParseMarkdown)
-> Generic ParseMarkdown
forall x. Rep ParseMarkdown x -> ParseMarkdown
forall x. ParseMarkdown -> Rep ParseMarkdown x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ParseMarkdown x -> ParseMarkdown
$cfrom :: forall x. ParseMarkdown -> Rep ParseMarkdown x
Generic)

-- | Parameter of Function getMarkdownText
data GetMarkdownText
  = -- | Replaces text entities with Markdown formatting in a human-friendly format. Entities that can't be represented in Markdown unambiguously are kept as is. This is an offline method. Can be called before authorization. Can be called synchronously
    GetMarkdownText
      { -- | The text
        GetMarkdownText -> FormattedText
text :: FormattedText
      }
  deriving (Int -> GetMarkdownText -> ShowS
[GetMarkdownText] -> ShowS
GetMarkdownText -> String
(Int -> GetMarkdownText -> ShowS)
-> (GetMarkdownText -> String)
-> ([GetMarkdownText] -> ShowS)
-> Show GetMarkdownText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMarkdownText] -> ShowS
$cshowList :: [GetMarkdownText] -> ShowS
show :: GetMarkdownText -> String
$cshow :: GetMarkdownText -> String
showsPrec :: Int -> GetMarkdownText -> ShowS
$cshowsPrec :: Int -> GetMarkdownText -> ShowS
Show, GetMarkdownText -> GetMarkdownText -> Bool
(GetMarkdownText -> GetMarkdownText -> Bool)
-> (GetMarkdownText -> GetMarkdownText -> Bool)
-> Eq GetMarkdownText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMarkdownText -> GetMarkdownText -> Bool
$c/= :: GetMarkdownText -> GetMarkdownText -> Bool
== :: GetMarkdownText -> GetMarkdownText -> Bool
$c== :: GetMarkdownText -> GetMarkdownText -> Bool
Eq, (forall x. GetMarkdownText -> Rep GetMarkdownText x)
-> (forall x. Rep GetMarkdownText x -> GetMarkdownText)
-> Generic GetMarkdownText
forall x. Rep GetMarkdownText x -> GetMarkdownText
forall x. GetMarkdownText -> Rep GetMarkdownText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMarkdownText x -> GetMarkdownText
$cfrom :: forall x. GetMarkdownText -> Rep GetMarkdownText x
Generic)

-- | Parameter of Function getFileMimeType
data GetFileMimeType
  = -- | Returns the MIME type of a file, guessed by its extension. Returns an empty string on failure. This is an offline method. Can be called before authorization. Can be called synchronously
    GetFileMimeType
      { -- | The name of the file or path to the file
        GetFileMimeType -> T
file_name :: T
      }
  deriving (Int -> GetFileMimeType -> ShowS
[GetFileMimeType] -> ShowS
GetFileMimeType -> String
(Int -> GetFileMimeType -> ShowS)
-> (GetFileMimeType -> String)
-> ([GetFileMimeType] -> ShowS)
-> Show GetFileMimeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileMimeType] -> ShowS
$cshowList :: [GetFileMimeType] -> ShowS
show :: GetFileMimeType -> String
$cshow :: GetFileMimeType -> String
showsPrec :: Int -> GetFileMimeType -> ShowS
$cshowsPrec :: Int -> GetFileMimeType -> ShowS
Show, GetFileMimeType -> GetFileMimeType -> Bool
(GetFileMimeType -> GetFileMimeType -> Bool)
-> (GetFileMimeType -> GetFileMimeType -> Bool)
-> Eq GetFileMimeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileMimeType -> GetFileMimeType -> Bool
$c/= :: GetFileMimeType -> GetFileMimeType -> Bool
== :: GetFileMimeType -> GetFileMimeType -> Bool
$c== :: GetFileMimeType -> GetFileMimeType -> Bool
Eq, (forall x. GetFileMimeType -> Rep GetFileMimeType x)
-> (forall x. Rep GetFileMimeType x -> GetFileMimeType)
-> Generic GetFileMimeType
forall x. Rep GetFileMimeType x -> GetFileMimeType
forall x. GetFileMimeType -> Rep GetFileMimeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFileMimeType x -> GetFileMimeType
$cfrom :: forall x. GetFileMimeType -> Rep GetFileMimeType x
Generic)

-- | Parameter of Function getFileExtension
data GetFileExtension
  = -- | Returns the extension of a file, guessed by its MIME type. Returns an empty string on failure. This is an offline method. Can be called before authorization. Can be called synchronously
    GetFileExtension
      { -- | The MIME type of the file
        GetFileExtension -> T
mime_type :: T
      }
  deriving (Int -> GetFileExtension -> ShowS
[GetFileExtension] -> ShowS
GetFileExtension -> String
(Int -> GetFileExtension -> ShowS)
-> (GetFileExtension -> String)
-> ([GetFileExtension] -> ShowS)
-> Show GetFileExtension
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileExtension] -> ShowS
$cshowList :: [GetFileExtension] -> ShowS
show :: GetFileExtension -> String
$cshow :: GetFileExtension -> String
showsPrec :: Int -> GetFileExtension -> ShowS
$cshowsPrec :: Int -> GetFileExtension -> ShowS
Show, GetFileExtension -> GetFileExtension -> Bool
(GetFileExtension -> GetFileExtension -> Bool)
-> (GetFileExtension -> GetFileExtension -> Bool)
-> Eq GetFileExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileExtension -> GetFileExtension -> Bool
$c/= :: GetFileExtension -> GetFileExtension -> Bool
== :: GetFileExtension -> GetFileExtension -> Bool
$c== :: GetFileExtension -> GetFileExtension -> Bool
Eq, (forall x. GetFileExtension -> Rep GetFileExtension x)
-> (forall x. Rep GetFileExtension x -> GetFileExtension)
-> Generic GetFileExtension
forall x. Rep GetFileExtension x -> GetFileExtension
forall x. GetFileExtension -> Rep GetFileExtension x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFileExtension x -> GetFileExtension
$cfrom :: forall x. GetFileExtension -> Rep GetFileExtension x
Generic)

-- | Parameter of Function cleanFileName
data CleanFileName
  = -- | Removes potentially dangerous characters from the name of a file. The encoding of the file name is supposed to be UTF-8. Returns an empty string on failure. This is an offline method. Can be called before authorization. Can be called synchronously
    CleanFileName
      { -- | File name or path to the file
        CleanFileName -> T
file_name :: T
      }
  deriving (Int -> CleanFileName -> ShowS
[CleanFileName] -> ShowS
CleanFileName -> String
(Int -> CleanFileName -> ShowS)
-> (CleanFileName -> String)
-> ([CleanFileName] -> ShowS)
-> Show CleanFileName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CleanFileName] -> ShowS
$cshowList :: [CleanFileName] -> ShowS
show :: CleanFileName -> String
$cshow :: CleanFileName -> String
showsPrec :: Int -> CleanFileName -> ShowS
$cshowsPrec :: Int -> CleanFileName -> ShowS
Show, CleanFileName -> CleanFileName -> Bool
(CleanFileName -> CleanFileName -> Bool)
-> (CleanFileName -> CleanFileName -> Bool) -> Eq CleanFileName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CleanFileName -> CleanFileName -> Bool
$c/= :: CleanFileName -> CleanFileName -> Bool
== :: CleanFileName -> CleanFileName -> Bool
$c== :: CleanFileName -> CleanFileName -> Bool
Eq, (forall x. CleanFileName -> Rep CleanFileName x)
-> (forall x. Rep CleanFileName x -> CleanFileName)
-> Generic CleanFileName
forall x. Rep CleanFileName x -> CleanFileName
forall x. CleanFileName -> Rep CleanFileName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CleanFileName x -> CleanFileName
$cfrom :: forall x. CleanFileName -> Rep CleanFileName x
Generic)

-- | Parameter of Function getLanguagePackString
data GetLanguagePackString
  = -- | Returns a string stored in the local database from the specified localization target and language pack by its key. Returns a 404 error if the string is not found. This is an offline method. Can be called before authorization. Can be called synchronously
    GetLanguagePackString
      { -- | Path to the language pack database in which strings are stored
        GetLanguagePackString -> T
language_pack_database_path :: T,
        -- | Localization target to which the language pack belongs
        GetLanguagePackString -> T
localization_target :: T,
        -- | Language pack identifier
        GetLanguagePackString -> T
language_pack_id :: T,
        -- | Language pack key of the string to be returned
        GetLanguagePackString -> T
key :: T
      }
  deriving (Int -> GetLanguagePackString -> ShowS
[GetLanguagePackString] -> ShowS
GetLanguagePackString -> String
(Int -> GetLanguagePackString -> ShowS)
-> (GetLanguagePackString -> String)
-> ([GetLanguagePackString] -> ShowS)
-> Show GetLanguagePackString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLanguagePackString] -> ShowS
$cshowList :: [GetLanguagePackString] -> ShowS
show :: GetLanguagePackString -> String
$cshow :: GetLanguagePackString -> String
showsPrec :: Int -> GetLanguagePackString -> ShowS
$cshowsPrec :: Int -> GetLanguagePackString -> ShowS
Show, GetLanguagePackString -> GetLanguagePackString -> Bool
(GetLanguagePackString -> GetLanguagePackString -> Bool)
-> (GetLanguagePackString -> GetLanguagePackString -> Bool)
-> Eq GetLanguagePackString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLanguagePackString -> GetLanguagePackString -> Bool
$c/= :: GetLanguagePackString -> GetLanguagePackString -> Bool
== :: GetLanguagePackString -> GetLanguagePackString -> Bool
$c== :: GetLanguagePackString -> GetLanguagePackString -> Bool
Eq, (forall x. GetLanguagePackString -> Rep GetLanguagePackString x)
-> (forall x. Rep GetLanguagePackString x -> GetLanguagePackString)
-> Generic GetLanguagePackString
forall x. Rep GetLanguagePackString x -> GetLanguagePackString
forall x. GetLanguagePackString -> Rep GetLanguagePackString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLanguagePackString x -> GetLanguagePackString
$cfrom :: forall x. GetLanguagePackString -> Rep GetLanguagePackString x
Generic)

-- | Parameter of Function getJsonValue
data GetJsonValue
  = -- | Converts a JSON-serialized string to corresponding JsonValue object. This is an offline method. Can be called before authorization. Can be called synchronously
    GetJsonValue
      { -- | The JSON-serialized string
        GetJsonValue -> T
json :: T
      }
  deriving (Int -> GetJsonValue -> ShowS
[GetJsonValue] -> ShowS
GetJsonValue -> String
(Int -> GetJsonValue -> ShowS)
-> (GetJsonValue -> String)
-> ([GetJsonValue] -> ShowS)
-> Show GetJsonValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJsonValue] -> ShowS
$cshowList :: [GetJsonValue] -> ShowS
show :: GetJsonValue -> String
$cshow :: GetJsonValue -> String
showsPrec :: Int -> GetJsonValue -> ShowS
$cshowsPrec :: Int -> GetJsonValue -> ShowS
Show, GetJsonValue -> GetJsonValue -> Bool
(GetJsonValue -> GetJsonValue -> Bool)
-> (GetJsonValue -> GetJsonValue -> Bool) -> Eq GetJsonValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJsonValue -> GetJsonValue -> Bool
$c/= :: GetJsonValue -> GetJsonValue -> Bool
== :: GetJsonValue -> GetJsonValue -> Bool
$c== :: GetJsonValue -> GetJsonValue -> Bool
Eq, (forall x. GetJsonValue -> Rep GetJsonValue x)
-> (forall x. Rep GetJsonValue x -> GetJsonValue)
-> Generic GetJsonValue
forall x. Rep GetJsonValue x -> GetJsonValue
forall x. GetJsonValue -> Rep GetJsonValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJsonValue x -> GetJsonValue
$cfrom :: forall x. GetJsonValue -> Rep GetJsonValue x
Generic)

-- | Parameter of Function getJsonString
data GetJsonString
  = -- | Converts a JsonValue object to corresponding JSON-serialized string. This is an offline method. Can be called before authorization. Can be called synchronously
    GetJsonString
      { -- | The JsonValue object
        GetJsonString -> JsonValue
json_value :: JsonValue
      }
  deriving (Int -> GetJsonString -> ShowS
[GetJsonString] -> ShowS
GetJsonString -> String
(Int -> GetJsonString -> ShowS)
-> (GetJsonString -> String)
-> ([GetJsonString] -> ShowS)
-> Show GetJsonString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetJsonString] -> ShowS
$cshowList :: [GetJsonString] -> ShowS
show :: GetJsonString -> String
$cshow :: GetJsonString -> String
showsPrec :: Int -> GetJsonString -> ShowS
$cshowsPrec :: Int -> GetJsonString -> ShowS
Show, GetJsonString -> GetJsonString -> Bool
(GetJsonString -> GetJsonString -> Bool)
-> (GetJsonString -> GetJsonString -> Bool) -> Eq GetJsonString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetJsonString -> GetJsonString -> Bool
$c/= :: GetJsonString -> GetJsonString -> Bool
== :: GetJsonString -> GetJsonString -> Bool
$c== :: GetJsonString -> GetJsonString -> Bool
Eq, (forall x. GetJsonString -> Rep GetJsonString x)
-> (forall x. Rep GetJsonString x -> GetJsonString)
-> Generic GetJsonString
forall x. Rep GetJsonString x -> GetJsonString
forall x. GetJsonString -> Rep GetJsonString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetJsonString x -> GetJsonString
$cfrom :: forall x. GetJsonString -> Rep GetJsonString x
Generic)

-- | Parameter of Function setPollAnswer
data SetPollAnswer
  = -- | Changes the user answer to a poll. A poll in quiz mode can be answered only once
    SetPollAnswer
      { -- | Identifier of the chat to which the poll belongs
        SetPollAnswer -> Int
chat_id :: I53,
        -- | Identifier of the message containing the poll
        SetPollAnswer -> Int
message_id :: I53,
        -- | 0-based identifiers of answer options, chosen by the user. User can choose more than 1 answer option only is the poll allows multiple answers
        SetPollAnswer -> [Int]
option_ids :: ([]) (I32)
      }
  deriving (Int -> SetPollAnswer -> ShowS
[SetPollAnswer] -> ShowS
SetPollAnswer -> String
(Int -> SetPollAnswer -> ShowS)
-> (SetPollAnswer -> String)
-> ([SetPollAnswer] -> ShowS)
-> Show SetPollAnswer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPollAnswer] -> ShowS
$cshowList :: [SetPollAnswer] -> ShowS
show :: SetPollAnswer -> String
$cshow :: SetPollAnswer -> String
showsPrec :: Int -> SetPollAnswer -> ShowS
$cshowsPrec :: Int -> SetPollAnswer -> ShowS
Show, SetPollAnswer -> SetPollAnswer -> Bool
(SetPollAnswer -> SetPollAnswer -> Bool)
-> (SetPollAnswer -> SetPollAnswer -> Bool) -> Eq SetPollAnswer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPollAnswer -> SetPollAnswer -> Bool
$c/= :: SetPollAnswer -> SetPollAnswer -> Bool
== :: SetPollAnswer -> SetPollAnswer -> Bool
$c== :: SetPollAnswer -> SetPollAnswer -> Bool
Eq, (forall x. SetPollAnswer -> Rep SetPollAnswer x)
-> (forall x. Rep SetPollAnswer x -> SetPollAnswer)
-> Generic SetPollAnswer
forall x. Rep SetPollAnswer x -> SetPollAnswer
forall x. SetPollAnswer -> Rep SetPollAnswer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetPollAnswer x -> SetPollAnswer
$cfrom :: forall x. SetPollAnswer -> Rep SetPollAnswer x
Generic)

-- | Parameter of Function getPollVoters
data GetPollVoters
  = -- | Returns users voted for the specified option in a non-anonymous polls. For the optimal performance the number of returned users is chosen by the library
    GetPollVoters
      { -- | Identifier of the chat to which the poll belongs
        GetPollVoters -> Int
chat_id :: I53,
        -- | Identifier of the message containing the poll
        GetPollVoters -> Int
message_id :: I53,
        -- | 0-based identifier of the answer option
        GetPollVoters -> Int
option_id :: I32,
        -- | Number of users to skip in the result; must be non-negative
        GetPollVoters -> Int
offset :: I32,
        -- | The maximum number of users to be returned; must be positive and can't be greater than 50. Fewer users may be returned than specified by the limit, even if the end of the voter list has not been reached
        GetPollVoters -> Int
limit :: I32
      }
  deriving (Int -> GetPollVoters -> ShowS
[GetPollVoters] -> ShowS
GetPollVoters -> String
(Int -> GetPollVoters -> ShowS)
-> (GetPollVoters -> String)
-> ([GetPollVoters] -> ShowS)
-> Show GetPollVoters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPollVoters] -> ShowS
$cshowList :: [GetPollVoters] -> ShowS
show :: GetPollVoters -> String
$cshow :: GetPollVoters -> String
showsPrec :: Int -> GetPollVoters -> ShowS
$cshowsPrec :: Int -> GetPollVoters -> ShowS
Show, GetPollVoters -> GetPollVoters -> Bool
(GetPollVoters -> GetPollVoters -> Bool)
-> (GetPollVoters -> GetPollVoters -> Bool) -> Eq GetPollVoters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPollVoters -> GetPollVoters -> Bool
$c/= :: GetPollVoters -> GetPollVoters -> Bool
== :: GetPollVoters -> GetPollVoters -> Bool
$c== :: GetPollVoters -> GetPollVoters -> Bool
Eq, (forall x. GetPollVoters -> Rep GetPollVoters x)
-> (forall x. Rep GetPollVoters x -> GetPollVoters)
-> Generic GetPollVoters
forall x. Rep GetPollVoters x -> GetPollVoters
forall x. GetPollVoters -> Rep GetPollVoters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPollVoters x -> GetPollVoters
$cfrom :: forall x. GetPollVoters -> Rep GetPollVoters x
Generic)

-- | Parameter of Function stopPoll
data StopPoll
  = -- | Stops a poll. A poll in a message can be stopped when the message has can_be_edited flag set
    StopPoll
      { -- | Identifier of the chat to which the poll belongs
        StopPoll -> Int
chat_id :: I53,
        -- | Identifier of the message containing the poll
        StopPoll -> Int
message_id :: I53,
        -- | The new message reply markup; for bots only
        StopPoll -> ReplyMarkup
reply_markup :: ReplyMarkup
      }
  deriving (Int -> StopPoll -> ShowS
[StopPoll] -> ShowS
StopPoll -> String
(Int -> StopPoll -> ShowS)
-> (StopPoll -> String) -> ([StopPoll] -> ShowS) -> Show StopPoll
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopPoll] -> ShowS
$cshowList :: [StopPoll] -> ShowS
show :: StopPoll -> String
$cshow :: StopPoll -> String
showsPrec :: Int -> StopPoll -> ShowS
$cshowsPrec :: Int -> StopPoll -> ShowS
Show, StopPoll -> StopPoll -> Bool
(StopPoll -> StopPoll -> Bool)
-> (StopPoll -> StopPoll -> Bool) -> Eq StopPoll
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopPoll -> StopPoll -> Bool
$c/= :: StopPoll -> StopPoll -> Bool
== :: StopPoll -> StopPoll -> Bool
$c== :: StopPoll -> StopPoll -> Bool
Eq, (forall x. StopPoll -> Rep StopPoll x)
-> (forall x. Rep StopPoll x -> StopPoll) -> Generic StopPoll
forall x. Rep StopPoll x -> StopPoll
forall x. StopPoll -> Rep StopPoll x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopPoll x -> StopPoll
$cfrom :: forall x. StopPoll -> Rep StopPoll x
Generic)

-- | Parameter of Function getLoginUrlInfo
data GetLoginUrlInfo
  = -- | Returns information about a button of type inlineKeyboardButtonTypeLoginUrl. The method needs to be called when the user presses the button
    GetLoginUrlInfo
      { -- | Chat identifier of the message with the button
        GetLoginUrlInfo -> Int
chat_id :: I53,
        -- | Message identifier of the message with the button
        GetLoginUrlInfo -> Int
message_id :: I53,
        -- | Button identifier
        GetLoginUrlInfo -> Int
button_id :: I32
      }
  deriving (Int -> GetLoginUrlInfo -> ShowS
[GetLoginUrlInfo] -> ShowS
GetLoginUrlInfo -> String
(Int -> GetLoginUrlInfo -> ShowS)
-> (GetLoginUrlInfo -> String)
-> ([GetLoginUrlInfo] -> ShowS)
-> Show GetLoginUrlInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoginUrlInfo] -> ShowS
$cshowList :: [GetLoginUrlInfo] -> ShowS
show :: GetLoginUrlInfo -> String
$cshow :: GetLoginUrlInfo -> String
showsPrec :: Int -> GetLoginUrlInfo -> ShowS
$cshowsPrec :: Int -> GetLoginUrlInfo -> ShowS
Show, GetLoginUrlInfo -> GetLoginUrlInfo -> Bool
(GetLoginUrlInfo -> GetLoginUrlInfo -> Bool)
-> (GetLoginUrlInfo -> GetLoginUrlInfo -> Bool)
-> Eq GetLoginUrlInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoginUrlInfo -> GetLoginUrlInfo -> Bool
$c/= :: GetLoginUrlInfo -> GetLoginUrlInfo -> Bool
== :: GetLoginUrlInfo -> GetLoginUrlInfo -> Bool
$c== :: GetLoginUrlInfo -> GetLoginUrlInfo -> Bool
Eq, (forall x. GetLoginUrlInfo -> Rep GetLoginUrlInfo x)
-> (forall x. Rep GetLoginUrlInfo x -> GetLoginUrlInfo)
-> Generic GetLoginUrlInfo
forall x. Rep GetLoginUrlInfo x -> GetLoginUrlInfo
forall x. GetLoginUrlInfo -> Rep GetLoginUrlInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoginUrlInfo x -> GetLoginUrlInfo
$cfrom :: forall x. GetLoginUrlInfo -> Rep GetLoginUrlInfo x
Generic)

-- | Parameter of Function getLoginUrl
data GetLoginUrl
  = -- | Returns an HTTP URL which can be used to automatically authorize the user on a website after clicking an inline button of type inlineKeyboardButtonTypeLoginUrl.
    GetLoginUrl
      { -- | Chat identifier of the message with the button
        GetLoginUrl -> Int
chat_id :: I53,
        -- | Message identifier of the message with the button
        GetLoginUrl -> Int
message_id :: I53,
        -- | Button identifier
        GetLoginUrl -> Int
button_id :: I32,
        -- | True, if the user allowed the bot to send them messages
        GetLoginUrl -> Bool
allow_write_access :: Bool
      }
  deriving (Int -> GetLoginUrl -> ShowS
[GetLoginUrl] -> ShowS
GetLoginUrl -> String
(Int -> GetLoginUrl -> ShowS)
-> (GetLoginUrl -> String)
-> ([GetLoginUrl] -> ShowS)
-> Show GetLoginUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLoginUrl] -> ShowS
$cshowList :: [GetLoginUrl] -> ShowS
show :: GetLoginUrl -> String
$cshow :: GetLoginUrl -> String
showsPrec :: Int -> GetLoginUrl -> ShowS
$cshowsPrec :: Int -> GetLoginUrl -> ShowS
Show, GetLoginUrl -> GetLoginUrl -> Bool
(GetLoginUrl -> GetLoginUrl -> Bool)
-> (GetLoginUrl -> GetLoginUrl -> Bool) -> Eq GetLoginUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLoginUrl -> GetLoginUrl -> Bool
$c/= :: GetLoginUrl -> GetLoginUrl -> Bool
== :: GetLoginUrl -> GetLoginUrl -> Bool
$c== :: GetLoginUrl -> GetLoginUrl -> Bool
Eq, (forall x. GetLoginUrl -> Rep GetLoginUrl x)
-> (forall x. Rep GetLoginUrl x -> GetLoginUrl)
-> Generic GetLoginUrl
forall x. Rep GetLoginUrl x -> GetLoginUrl
forall x. GetLoginUrl -> Rep GetLoginUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLoginUrl x -> GetLoginUrl
$cfrom :: forall x. GetLoginUrl -> Rep GetLoginUrl x
Generic)

-- | Parameter of Function getInlineQueryResults
data GetInlineQueryResults
  = -- | Sends an inline query to a bot and returns its results. Returns an error with code 502 if the bot fails to answer the query before the query timeout expires
    GetInlineQueryResults
      { -- | The identifier of the target bot
        GetInlineQueryResults -> Int
bot_user_id :: I32,
        -- | Identifier of the chat where the query was sent
        GetInlineQueryResults -> Int
chat_id :: I53,
        -- | Location of the user, only if needed
        GetInlineQueryResults -> Location
user_location :: Location,
        -- | Text of the query
        GetInlineQueryResults -> T
query :: T,
        -- | Offset of the first entry to return
        GetInlineQueryResults -> T
offset :: T
      }
  deriving (Int -> GetInlineQueryResults -> ShowS
[GetInlineQueryResults] -> ShowS
GetInlineQueryResults -> String
(Int -> GetInlineQueryResults -> ShowS)
-> (GetInlineQueryResults -> String)
-> ([GetInlineQueryResults] -> ShowS)
-> Show GetInlineQueryResults
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInlineQueryResults] -> ShowS
$cshowList :: [GetInlineQueryResults] -> ShowS
show :: GetInlineQueryResults -> String
$cshow :: GetInlineQueryResults -> String
showsPrec :: Int -> GetInlineQueryResults -> ShowS
$cshowsPrec :: Int -> GetInlineQueryResults -> ShowS
Show, GetInlineQueryResults -> GetInlineQueryResults -> Bool
(GetInlineQueryResults -> GetInlineQueryResults -> Bool)
-> (GetInlineQueryResults -> GetInlineQueryResults -> Bool)
-> Eq GetInlineQueryResults
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInlineQueryResults -> GetInlineQueryResults -> Bool
$c/= :: GetInlineQueryResults -> GetInlineQueryResults -> Bool
== :: GetInlineQueryResults -> GetInlineQueryResults -> Bool
$c== :: GetInlineQueryResults -> GetInlineQueryResults -> Bool
Eq, (forall x. GetInlineQueryResults -> Rep GetInlineQueryResults x)
-> (forall x. Rep GetInlineQueryResults x -> GetInlineQueryResults)
-> Generic GetInlineQueryResults
forall x. Rep GetInlineQueryResults x -> GetInlineQueryResults
forall x. GetInlineQueryResults -> Rep GetInlineQueryResults x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInlineQueryResults x -> GetInlineQueryResults
$cfrom :: forall x. GetInlineQueryResults -> Rep GetInlineQueryResults x
Generic)

-- | Parameter of Function answerInlineQuery
data AnswerInlineQuery
  = -- | Sets the result of an inline query; for bots only
    AnswerInlineQuery
      { -- | Identifier of the inline query
        AnswerInlineQuery -> I64
inline_query_id :: I64,
        -- | True, if the result of the query can be cached for the specified user
        AnswerInlineQuery -> Bool
is_personal :: Bool,
        -- | The results of the query
        AnswerInlineQuery -> [InputInlineQueryResult]
results :: ([]) (InputInlineQueryResult),
        -- | Allowed time to cache the results of the query, in seconds
        AnswerInlineQuery -> Int
cache_time :: I32,
        -- | Offset for the next inline query; pass an empty string if there are no more results
        AnswerInlineQuery -> T
next_offset :: T,
        -- | If non-empty, this text should be shown on the button that opens a private chat with the bot and sends a start message to the bot with the parameter switch_pm_parameter
        AnswerInlineQuery -> T
switch_pm_text :: T,
        -- | The parameter for the bot start message
        AnswerInlineQuery -> T
switch_pm_parameter :: T
      }
  deriving (Int -> AnswerInlineQuery -> ShowS
[AnswerInlineQuery] -> ShowS
AnswerInlineQuery -> String
(Int -> AnswerInlineQuery -> ShowS)
-> (AnswerInlineQuery -> String)
-> ([AnswerInlineQuery] -> ShowS)
-> Show AnswerInlineQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnswerInlineQuery] -> ShowS
$cshowList :: [AnswerInlineQuery] -> ShowS
show :: AnswerInlineQuery -> String
$cshow :: AnswerInlineQuery -> String
showsPrec :: Int -> AnswerInlineQuery -> ShowS
$cshowsPrec :: Int -> AnswerInlineQuery -> ShowS
Show, AnswerInlineQuery -> AnswerInlineQuery -> Bool
(AnswerInlineQuery -> AnswerInlineQuery -> Bool)
-> (AnswerInlineQuery -> AnswerInlineQuery -> Bool)
-> Eq AnswerInlineQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnswerInlineQuery -> AnswerInlineQuery -> Bool
$c/= :: AnswerInlineQuery -> AnswerInlineQuery -> Bool
== :: AnswerInlineQuery -> AnswerInlineQuery -> Bool
$c== :: AnswerInlineQuery -> AnswerInlineQuery -> Bool
Eq, (forall x. AnswerInlineQuery -> Rep AnswerInlineQuery x)
-> (forall x. Rep AnswerInlineQuery x -> AnswerInlineQuery)
-> Generic AnswerInlineQuery
forall x. Rep AnswerInlineQuery x -> AnswerInlineQuery
forall x. AnswerInlineQuery -> Rep AnswerInlineQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnswerInlineQuery x -> AnswerInlineQuery
$cfrom :: forall x. AnswerInlineQuery -> Rep AnswerInlineQuery x
Generic)

-- | Parameter of Function getCallbackQueryAnswer
data GetCallbackQueryAnswer
  = -- | Sends a callback query to a bot and returns an answer. Returns an error with code 502 if the bot fails to answer the query before the query timeout expires
    GetCallbackQueryAnswer
      { -- | Identifier of the chat with the message
        GetCallbackQueryAnswer -> Int
chat_id :: I53,
        -- | Identifier of the message from which the query originated
        GetCallbackQueryAnswer -> Int
message_id :: I53,
        -- | Query payload
        GetCallbackQueryAnswer -> CallbackQueryPayload
payload :: CallbackQueryPayload
      }
  deriving (Int -> GetCallbackQueryAnswer -> ShowS
[GetCallbackQueryAnswer] -> ShowS
GetCallbackQueryAnswer -> String
(Int -> GetCallbackQueryAnswer -> ShowS)
-> (GetCallbackQueryAnswer -> String)
-> ([GetCallbackQueryAnswer] -> ShowS)
-> Show GetCallbackQueryAnswer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCallbackQueryAnswer] -> ShowS
$cshowList :: [GetCallbackQueryAnswer] -> ShowS
show :: GetCallbackQueryAnswer -> String
$cshow :: GetCallbackQueryAnswer -> String
showsPrec :: Int -> GetCallbackQueryAnswer -> ShowS
$cshowsPrec :: Int -> GetCallbackQueryAnswer -> ShowS
Show, GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool
(GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool)
-> (GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool)
-> Eq GetCallbackQueryAnswer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool
$c/= :: GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool
== :: GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool
$c== :: GetCallbackQueryAnswer -> GetCallbackQueryAnswer -> Bool
Eq, (forall x. GetCallbackQueryAnswer -> Rep GetCallbackQueryAnswer x)
-> (forall x.
    Rep GetCallbackQueryAnswer x -> GetCallbackQueryAnswer)
-> Generic GetCallbackQueryAnswer
forall x. Rep GetCallbackQueryAnswer x -> GetCallbackQueryAnswer
forall x. GetCallbackQueryAnswer -> Rep GetCallbackQueryAnswer x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCallbackQueryAnswer x -> GetCallbackQueryAnswer
$cfrom :: forall x. GetCallbackQueryAnswer -> Rep GetCallbackQueryAnswer x
Generic)

-- | Parameter of Function answerCallbackQuery
data AnswerCallbackQuery
  = -- | Sets the result of a callback query; for bots only
    AnswerCallbackQuery
      { -- | Identifier of the callback query
        AnswerCallbackQuery -> I64
callback_query_id :: I64,
        -- | Text of the answer
        AnswerCallbackQuery -> T
text :: T,
        -- | If true, an alert should be shown to the user instead of a toast notification
        AnswerCallbackQuery -> Bool
show_alert :: Bool,
        -- | URL to be opened
        AnswerCallbackQuery -> T
url :: T,
        -- | Time during which the result of the query can be cached, in seconds
        AnswerCallbackQuery -> Int
cache_time :: I32
      }
  deriving (Int -> AnswerCallbackQuery -> ShowS
[AnswerCallbackQuery] -> ShowS
AnswerCallbackQuery -> String
(Int -> AnswerCallbackQuery -> ShowS)
-> (AnswerCallbackQuery -> String)
-> ([AnswerCallbackQuery] -> ShowS)
-> Show AnswerCallbackQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnswerCallbackQuery] -> ShowS
$cshowList :: [AnswerCallbackQuery] -> ShowS
show :: AnswerCallbackQuery -> String
$cshow :: AnswerCallbackQuery -> String
showsPrec :: Int -> AnswerCallbackQuery -> ShowS
$cshowsPrec :: Int -> AnswerCallbackQuery -> ShowS
Show, AnswerCallbackQuery -> AnswerCallbackQuery -> Bool
(AnswerCallbackQuery -> AnswerCallbackQuery -> Bool)
-> (AnswerCallbackQuery -> AnswerCallbackQuery -> Bool)
-> Eq AnswerCallbackQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnswerCallbackQuery -> AnswerCallbackQuery -> Bool
$c/= :: AnswerCallbackQuery -> AnswerCallbackQuery -> Bool
== :: AnswerCallbackQuery -> AnswerCallbackQuery -> Bool
$c== :: AnswerCallbackQuery -> AnswerCallbackQuery -> Bool
Eq, (forall x. AnswerCallbackQuery -> Rep AnswerCallbackQuery x)
-> (forall x. Rep AnswerCallbackQuery x -> AnswerCallbackQuery)
-> Generic AnswerCallbackQuery
forall x. Rep AnswerCallbackQuery x -> AnswerCallbackQuery
forall x. AnswerCallbackQuery -> Rep AnswerCallbackQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnswerCallbackQuery x -> AnswerCallbackQuery
$cfrom :: forall x. AnswerCallbackQuery -> Rep AnswerCallbackQuery x
Generic)

-- | Parameter of Function answerShippingQuery
data AnswerShippingQuery
  = -- | Sets the result of a shipping query; for bots only
    AnswerShippingQuery
      { -- | Identifier of the shipping query
        AnswerShippingQuery -> I64
shipping_query_id :: I64,
        -- | Available shipping options
        AnswerShippingQuery -> [ShippingOption]
shipping_options :: ([]) (ShippingOption),
        -- | An error message, empty on success
        AnswerShippingQuery -> T
error_message :: T
      }
  deriving (Int -> AnswerShippingQuery -> ShowS
[AnswerShippingQuery] -> ShowS
AnswerShippingQuery -> String
(Int -> AnswerShippingQuery -> ShowS)
-> (AnswerShippingQuery -> String)
-> ([AnswerShippingQuery] -> ShowS)
-> Show AnswerShippingQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnswerShippingQuery] -> ShowS
$cshowList :: [AnswerShippingQuery] -> ShowS
show :: AnswerShippingQuery -> String
$cshow :: AnswerShippingQuery -> String
showsPrec :: Int -> AnswerShippingQuery -> ShowS
$cshowsPrec :: Int -> AnswerShippingQuery -> ShowS
Show, AnswerShippingQuery -> AnswerShippingQuery -> Bool
(AnswerShippingQuery -> AnswerShippingQuery -> Bool)
-> (AnswerShippingQuery -> AnswerShippingQuery -> Bool)
-> Eq AnswerShippingQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnswerShippingQuery -> AnswerShippingQuery -> Bool
$c/= :: AnswerShippingQuery -> AnswerShippingQuery -> Bool
== :: AnswerShippingQuery -> AnswerShippingQuery -> Bool
$c== :: AnswerShippingQuery -> AnswerShippingQuery -> Bool
Eq, (forall x. AnswerShippingQuery -> Rep AnswerShippingQuery x)
-> (forall x. Rep AnswerShippingQuery x -> AnswerShippingQuery)
-> Generic AnswerShippingQuery
forall x. Rep AnswerShippingQuery x -> AnswerShippingQuery
forall x. AnswerShippingQuery -> Rep AnswerShippingQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnswerShippingQuery x -> AnswerShippingQuery
$cfrom :: forall x. AnswerShippingQuery -> Rep AnswerShippingQuery x
Generic)

-- | Parameter of Function answerPreCheckoutQuery
data AnswerPreCheckoutQuery
  = -- | Sets the result of a pre-checkout query; for bots only
    AnswerPreCheckoutQuery
      { -- | Identifier of the pre-checkout query
        AnswerPreCheckoutQuery -> I64
pre_checkout_query_id :: I64,
        -- | An error message, empty on success
        AnswerPreCheckoutQuery -> T
error_message :: T
      }
  deriving (Int -> AnswerPreCheckoutQuery -> ShowS
[AnswerPreCheckoutQuery] -> ShowS
AnswerPreCheckoutQuery -> String
(Int -> AnswerPreCheckoutQuery -> ShowS)
-> (AnswerPreCheckoutQuery -> String)
-> ([AnswerPreCheckoutQuery] -> ShowS)
-> Show AnswerPreCheckoutQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnswerPreCheckoutQuery] -> ShowS
$cshowList :: [AnswerPreCheckoutQuery] -> ShowS
show :: AnswerPreCheckoutQuery -> String
$cshow :: AnswerPreCheckoutQuery -> String
showsPrec :: Int -> AnswerPreCheckoutQuery -> ShowS
$cshowsPrec :: Int -> AnswerPreCheckoutQuery -> ShowS
Show, AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool
(AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool)
-> (AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool)
-> Eq AnswerPreCheckoutQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool
$c/= :: AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool
== :: AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool
$c== :: AnswerPreCheckoutQuery -> AnswerPreCheckoutQuery -> Bool
Eq, (forall x. AnswerPreCheckoutQuery -> Rep AnswerPreCheckoutQuery x)
-> (forall x.
    Rep AnswerPreCheckoutQuery x -> AnswerPreCheckoutQuery)
-> Generic AnswerPreCheckoutQuery
forall x. Rep AnswerPreCheckoutQuery x -> AnswerPreCheckoutQuery
forall x. AnswerPreCheckoutQuery -> Rep AnswerPreCheckoutQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnswerPreCheckoutQuery x -> AnswerPreCheckoutQuery
$cfrom :: forall x. AnswerPreCheckoutQuery -> Rep AnswerPreCheckoutQuery x
Generic)

-- | Parameter of Function setGameScore
data SetGameScore
  = -- | Updates the game score of the specified user in the game; for bots only
    SetGameScore
      { -- | The chat to which the message with the game belongs
        SetGameScore -> Int
chat_id :: I53,
        -- | Identifier of the message
        SetGameScore -> Int
message_id :: I53,
        -- | True, if the message should be edited
        SetGameScore -> Bool
edit_message :: Bool,
        -- | User identifier
        SetGameScore -> Int
user_id :: I32,
        -- | The new score
        SetGameScore -> Int
score :: I32,
        -- | Pass true to update the score even if it decreases. If the score is 0, the user will be deleted from the high score table
        SetGameScore -> Bool
force :: Bool
      }
  deriving (Int -> SetGameScore -> ShowS
[SetGameScore] -> ShowS
SetGameScore -> String
(Int -> SetGameScore -> ShowS)
-> (SetGameScore -> String)
-> ([SetGameScore] -> ShowS)
-> Show SetGameScore
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetGameScore] -> ShowS
$cshowList :: [SetGameScore] -> ShowS
show :: SetGameScore -> String
$cshow :: SetGameScore -> String
showsPrec :: Int -> SetGameScore -> ShowS
$cshowsPrec :: Int -> SetGameScore -> ShowS
Show, SetGameScore -> SetGameScore -> Bool
(SetGameScore -> SetGameScore -> Bool)
-> (SetGameScore -> SetGameScore -> Bool) -> Eq SetGameScore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetGameScore -> SetGameScore -> Bool
$c/= :: SetGameScore -> SetGameScore -> Bool
== :: SetGameScore -> SetGameScore -> Bool
$c== :: SetGameScore -> SetGameScore -> Bool
Eq, (forall x. SetGameScore -> Rep SetGameScore x)
-> (forall x. Rep SetGameScore x -> SetGameScore)
-> Generic SetGameScore
forall x. Rep SetGameScore x -> SetGameScore
forall x. SetGameScore -> Rep SetGameScore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetGameScore x -> SetGameScore
$cfrom :: forall x. SetGameScore -> Rep SetGameScore x
Generic)

-- | Parameter of Function setInlineGameScore
data SetInlineGameScore
  = -- | Updates the game score of the specified user in a game; for bots only
    SetInlineGameScore
      { -- | Inline message identifier
        SetInlineGameScore -> T
inline_message_id :: T,
        -- | True, if the message should be edited
        SetInlineGameScore -> Bool
edit_message :: Bool,
        -- | User identifier
        SetInlineGameScore -> Int
user_id :: I32,
        -- | The new score
        SetInlineGameScore -> Int
score :: I32,
        -- | Pass true to update the score even if it decreases. If the score is 0, the user will be deleted from the high score table
        SetInlineGameScore -> Bool
force :: Bool
      }
  deriving (Int -> SetInlineGameScore -> ShowS
[SetInlineGameScore] -> ShowS
SetInlineGameScore -> String
(Int -> SetInlineGameScore -> ShowS)
-> (SetInlineGameScore -> String)
-> ([SetInlineGameScore] -> ShowS)
-> Show SetInlineGameScore
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetInlineGameScore] -> ShowS
$cshowList :: [SetInlineGameScore] -> ShowS
show :: SetInlineGameScore -> String
$cshow :: SetInlineGameScore -> String
showsPrec :: Int -> SetInlineGameScore -> ShowS
$cshowsPrec :: Int -> SetInlineGameScore -> ShowS
Show, SetInlineGameScore -> SetInlineGameScore -> Bool
(SetInlineGameScore -> SetInlineGameScore -> Bool)
-> (SetInlineGameScore -> SetInlineGameScore -> Bool)
-> Eq SetInlineGameScore
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetInlineGameScore -> SetInlineGameScore -> Bool
$c/= :: SetInlineGameScore -> SetInlineGameScore -> Bool
== :: SetInlineGameScore -> SetInlineGameScore -> Bool
$c== :: SetInlineGameScore -> SetInlineGameScore -> Bool
Eq, (forall x. SetInlineGameScore -> Rep SetInlineGameScore x)
-> (forall x. Rep SetInlineGameScore x -> SetInlineGameScore)
-> Generic SetInlineGameScore
forall x. Rep SetInlineGameScore x -> SetInlineGameScore
forall x. SetInlineGameScore -> Rep SetInlineGameScore x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetInlineGameScore x -> SetInlineGameScore
$cfrom :: forall x. SetInlineGameScore -> Rep SetInlineGameScore x
Generic)

-- | Parameter of Function getGameHighScores
data GetGameHighScores
  = -- | Returns the high scores for a game and some part of the high score table in the range of the specified user; for bots only
    GetGameHighScores
      { -- | The chat that contains the message with the game
        GetGameHighScores -> Int
chat_id :: I53,
        -- | Identifier of the message
        GetGameHighScores -> Int
message_id :: I53,
        -- | User identifier
        GetGameHighScores -> Int
user_id :: I32
      }
  deriving (Int -> GetGameHighScores -> ShowS
[GetGameHighScores] -> ShowS
GetGameHighScores -> String
(Int -> GetGameHighScores -> ShowS)
-> (GetGameHighScores -> String)
-> ([GetGameHighScores] -> ShowS)
-> Show GetGameHighScores
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetGameHighScores] -> ShowS
$cshowList :: [GetGameHighScores] -> ShowS
show :: GetGameHighScores -> String
$cshow :: GetGameHighScores -> String
showsPrec :: Int -> GetGameHighScores -> ShowS
$cshowsPrec :: Int -> GetGameHighScores -> ShowS
Show, GetGameHighScores -> GetGameHighScores -> Bool
(GetGameHighScores -> GetGameHighScores -> Bool)
-> (GetGameHighScores -> GetGameHighScores -> Bool)
-> Eq GetGameHighScores
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetGameHighScores -> GetGameHighScores -> Bool
$c/= :: GetGameHighScores -> GetGameHighScores -> Bool
== :: GetGameHighScores -> GetGameHighScores -> Bool
$c== :: GetGameHighScores -> GetGameHighScores -> Bool
Eq, (forall x. GetGameHighScores -> Rep GetGameHighScores x)
-> (forall x. Rep GetGameHighScores x -> GetGameHighScores)
-> Generic GetGameHighScores
forall x. Rep GetGameHighScores x -> GetGameHighScores
forall x. GetGameHighScores -> Rep GetGameHighScores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetGameHighScores x -> GetGameHighScores
$cfrom :: forall x. GetGameHighScores -> Rep GetGameHighScores x
Generic)

-- | Parameter of Function getInlineGameHighScores
data GetInlineGameHighScores
  = -- | Returns game high scores and some part of the high score table in the range of the specified user; for bots only
    GetInlineGameHighScores
      { -- | Inline message identifier
        GetInlineGameHighScores -> T
inline_message_id :: T,
        -- | User identifier
        GetInlineGameHighScores -> Int
user_id :: I32
      }
  deriving (Int -> GetInlineGameHighScores -> ShowS
[GetInlineGameHighScores] -> ShowS
GetInlineGameHighScores -> String
(Int -> GetInlineGameHighScores -> ShowS)
-> (GetInlineGameHighScores -> String)
-> ([GetInlineGameHighScores] -> ShowS)
-> Show GetInlineGameHighScores
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInlineGameHighScores] -> ShowS
$cshowList :: [GetInlineGameHighScores] -> ShowS
show :: GetInlineGameHighScores -> String
$cshow :: GetInlineGameHighScores -> String
showsPrec :: Int -> GetInlineGameHighScores -> ShowS
$cshowsPrec :: Int -> GetInlineGameHighScores -> ShowS
Show, GetInlineGameHighScores -> GetInlineGameHighScores -> Bool
(GetInlineGameHighScores -> GetInlineGameHighScores -> Bool)
-> (GetInlineGameHighScores -> GetInlineGameHighScores -> Bool)
-> Eq GetInlineGameHighScores
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInlineGameHighScores -> GetInlineGameHighScores -> Bool
$c/= :: GetInlineGameHighScores -> GetInlineGameHighScores -> Bool
== :: GetInlineGameHighScores -> GetInlineGameHighScores -> Bool
$c== :: GetInlineGameHighScores -> GetInlineGameHighScores -> Bool
Eq, (forall x.
 GetInlineGameHighScores -> Rep GetInlineGameHighScores x)
-> (forall x.
    Rep GetInlineGameHighScores x -> GetInlineGameHighScores)
-> Generic GetInlineGameHighScores
forall x. Rep GetInlineGameHighScores x -> GetInlineGameHighScores
forall x. GetInlineGameHighScores -> Rep GetInlineGameHighScores x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInlineGameHighScores x -> GetInlineGameHighScores
$cfrom :: forall x. GetInlineGameHighScores -> Rep GetInlineGameHighScores x
Generic)

-- | Parameter of Function deleteChatReplyMarkup
data DeleteChatReplyMarkup
  = -- | Deletes the default reply markup from a chat. Must be called after a one-time keyboard or a ForceReply reply markup has been used. UpdateChatReplyMarkup will be sent if the reply markup will be changed
    DeleteChatReplyMarkup
      { -- | Chat identifier
        DeleteChatReplyMarkup -> Int
chat_id :: I53,
        -- | The message identifier of the used keyboard
        DeleteChatReplyMarkup -> Int
message_id :: I53
      }
  deriving (Int -> DeleteChatReplyMarkup -> ShowS
[DeleteChatReplyMarkup] -> ShowS
DeleteChatReplyMarkup -> String
(Int -> DeleteChatReplyMarkup -> ShowS)
-> (DeleteChatReplyMarkup -> String)
-> ([DeleteChatReplyMarkup] -> ShowS)
-> Show DeleteChatReplyMarkup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteChatReplyMarkup] -> ShowS
$cshowList :: [DeleteChatReplyMarkup] -> ShowS
show :: DeleteChatReplyMarkup -> String
$cshow :: DeleteChatReplyMarkup -> String
showsPrec :: Int -> DeleteChatReplyMarkup -> ShowS
$cshowsPrec :: Int -> DeleteChatReplyMarkup -> ShowS
Show, DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool
(DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool)
-> (DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool)
-> Eq DeleteChatReplyMarkup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool
$c/= :: DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool
== :: DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool
$c== :: DeleteChatReplyMarkup -> DeleteChatReplyMarkup -> Bool
Eq, (forall x. DeleteChatReplyMarkup -> Rep DeleteChatReplyMarkup x)
-> (forall x. Rep DeleteChatReplyMarkup x -> DeleteChatReplyMarkup)
-> Generic DeleteChatReplyMarkup
forall x. Rep DeleteChatReplyMarkup x -> DeleteChatReplyMarkup
forall x. DeleteChatReplyMarkup -> Rep DeleteChatReplyMarkup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteChatReplyMarkup x -> DeleteChatReplyMarkup
$cfrom :: forall x. DeleteChatReplyMarkup -> Rep DeleteChatReplyMarkup x
Generic)

-- | Parameter of Function sendChatAction
data SendChatAction
  = -- | Sends a notification about user activity in a chat
    SendChatAction
      { -- | Chat identifier
        SendChatAction -> Int
chat_id :: I53,
        -- | The action description
        SendChatAction -> ChatAction
action :: ChatAction
      }
  deriving (Int -> SendChatAction -> ShowS
[SendChatAction] -> ShowS
SendChatAction -> String
(Int -> SendChatAction -> ShowS)
-> (SendChatAction -> String)
-> ([SendChatAction] -> ShowS)
-> Show SendChatAction
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendChatAction] -> ShowS
$cshowList :: [SendChatAction] -> ShowS
show :: SendChatAction -> String
$cshow :: SendChatAction -> String
showsPrec :: Int -> SendChatAction -> ShowS
$cshowsPrec :: Int -> SendChatAction -> ShowS
Show, SendChatAction -> SendChatAction -> Bool
(SendChatAction -> SendChatAction -> Bool)
-> (SendChatAction -> SendChatAction -> Bool) -> Eq SendChatAction
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendChatAction -> SendChatAction -> Bool
$c/= :: SendChatAction -> SendChatAction -> Bool
== :: SendChatAction -> SendChatAction -> Bool
$c== :: SendChatAction -> SendChatAction -> Bool
Eq, (forall x. SendChatAction -> Rep SendChatAction x)
-> (forall x. Rep SendChatAction x -> SendChatAction)
-> Generic SendChatAction
forall x. Rep SendChatAction x -> SendChatAction
forall x. SendChatAction -> Rep SendChatAction x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendChatAction x -> SendChatAction
$cfrom :: forall x. SendChatAction -> Rep SendChatAction x
Generic)

-- | Parameter of Function openChat
data OpenChat
  = -- | Informs TDLib that the chat is opened by the user. Many useful activities depend on the chat being opened or closed (e.g., in supergroups and channels all updates are received only for opened chats)
    OpenChat
      { -- | Chat identifier
        OpenChat -> Int
chat_id :: I53
      }
  deriving (Int -> OpenChat -> ShowS
[OpenChat] -> ShowS
OpenChat -> String
(Int -> OpenChat -> ShowS)
-> (OpenChat -> String) -> ([OpenChat] -> ShowS) -> Show OpenChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenChat] -> ShowS
$cshowList :: [OpenChat] -> ShowS
show :: OpenChat -> String
$cshow :: OpenChat -> String
showsPrec :: Int -> OpenChat -> ShowS
$cshowsPrec :: Int -> OpenChat -> ShowS
Show, OpenChat -> OpenChat -> Bool
(OpenChat -> OpenChat -> Bool)
-> (OpenChat -> OpenChat -> Bool) -> Eq OpenChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenChat -> OpenChat -> Bool
$c/= :: OpenChat -> OpenChat -> Bool
== :: OpenChat -> OpenChat -> Bool
$c== :: OpenChat -> OpenChat -> Bool
Eq, (forall x. OpenChat -> Rep OpenChat x)
-> (forall x. Rep OpenChat x -> OpenChat) -> Generic OpenChat
forall x. Rep OpenChat x -> OpenChat
forall x. OpenChat -> Rep OpenChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenChat x -> OpenChat
$cfrom :: forall x. OpenChat -> Rep OpenChat x
Generic)

-- | Parameter of Function closeChat
data CloseChat
  = -- | Informs TDLib that the chat is closed by the user. Many useful activities depend on the chat being opened or closed
    CloseChat
      { -- | Chat identifier
        CloseChat -> Int
chat_id :: I53
      }
  deriving (Int -> CloseChat -> ShowS
[CloseChat] -> ShowS
CloseChat -> String
(Int -> CloseChat -> ShowS)
-> (CloseChat -> String)
-> ([CloseChat] -> ShowS)
-> Show CloseChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CloseChat] -> ShowS
$cshowList :: [CloseChat] -> ShowS
show :: CloseChat -> String
$cshow :: CloseChat -> String
showsPrec :: Int -> CloseChat -> ShowS
$cshowsPrec :: Int -> CloseChat -> ShowS
Show, CloseChat -> CloseChat -> Bool
(CloseChat -> CloseChat -> Bool)
-> (CloseChat -> CloseChat -> Bool) -> Eq CloseChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CloseChat -> CloseChat -> Bool
$c/= :: CloseChat -> CloseChat -> Bool
== :: CloseChat -> CloseChat -> Bool
$c== :: CloseChat -> CloseChat -> Bool
Eq, (forall x. CloseChat -> Rep CloseChat x)
-> (forall x. Rep CloseChat x -> CloseChat) -> Generic CloseChat
forall x. Rep CloseChat x -> CloseChat
forall x. CloseChat -> Rep CloseChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CloseChat x -> CloseChat
$cfrom :: forall x. CloseChat -> Rep CloseChat x
Generic)

-- | Parameter of Function viewMessages
data ViewMessages
  = -- | Informs TDLib that messages are being viewed by the user. Many useful activities depend on whether the messages are currently being viewed or not (e.g., marking messages as read, incrementing a view counter, updating a view counter, removing deleted messages in supergroups and channels)
    ViewMessages
      { -- | Chat identifier
        ViewMessages -> Int
chat_id :: I53,
        -- | The identifiers of the messages being viewed
        ViewMessages -> [Int]
message_ids :: ([]) (I53),
        -- | True, if messages in closed chats should be marked as read
        ViewMessages -> Bool
force_read :: Bool
      }
  deriving (Int -> ViewMessages -> ShowS
[ViewMessages] -> ShowS
ViewMessages -> String
(Int -> ViewMessages -> ShowS)
-> (ViewMessages -> String)
-> ([ViewMessages] -> ShowS)
-> Show ViewMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ViewMessages] -> ShowS
$cshowList :: [ViewMessages] -> ShowS
show :: ViewMessages -> String
$cshow :: ViewMessages -> String
showsPrec :: Int -> ViewMessages -> ShowS
$cshowsPrec :: Int -> ViewMessages -> ShowS
Show, ViewMessages -> ViewMessages -> Bool
(ViewMessages -> ViewMessages -> Bool)
-> (ViewMessages -> ViewMessages -> Bool) -> Eq ViewMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ViewMessages -> ViewMessages -> Bool
$c/= :: ViewMessages -> ViewMessages -> Bool
== :: ViewMessages -> ViewMessages -> Bool
$c== :: ViewMessages -> ViewMessages -> Bool
Eq, (forall x. ViewMessages -> Rep ViewMessages x)
-> (forall x. Rep ViewMessages x -> ViewMessages)
-> Generic ViewMessages
forall x. Rep ViewMessages x -> ViewMessages
forall x. ViewMessages -> Rep ViewMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ViewMessages x -> ViewMessages
$cfrom :: forall x. ViewMessages -> Rep ViewMessages x
Generic)

-- | Parameter of Function openMessageContent
data OpenMessageContent
  = -- | Informs TDLib that the message content has been opened (e.g., the user has opened a photo, video, document, location or venue, or has listened to an audio file or voice note message). An updateMessageContentOpened update will be generated if something has changed
    OpenMessageContent
      { -- | Chat identifier of the message
        OpenMessageContent -> Int
chat_id :: I53,
        -- | Identifier of the message with the opened content
        OpenMessageContent -> Int
message_id :: I53
      }
  deriving (Int -> OpenMessageContent -> ShowS
[OpenMessageContent] -> ShowS
OpenMessageContent -> String
(Int -> OpenMessageContent -> ShowS)
-> (OpenMessageContent -> String)
-> ([OpenMessageContent] -> ShowS)
-> Show OpenMessageContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OpenMessageContent] -> ShowS
$cshowList :: [OpenMessageContent] -> ShowS
show :: OpenMessageContent -> String
$cshow :: OpenMessageContent -> String
showsPrec :: Int -> OpenMessageContent -> ShowS
$cshowsPrec :: Int -> OpenMessageContent -> ShowS
Show, OpenMessageContent -> OpenMessageContent -> Bool
(OpenMessageContent -> OpenMessageContent -> Bool)
-> (OpenMessageContent -> OpenMessageContent -> Bool)
-> Eq OpenMessageContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenMessageContent -> OpenMessageContent -> Bool
$c/= :: OpenMessageContent -> OpenMessageContent -> Bool
== :: OpenMessageContent -> OpenMessageContent -> Bool
$c== :: OpenMessageContent -> OpenMessageContent -> Bool
Eq, (forall x. OpenMessageContent -> Rep OpenMessageContent x)
-> (forall x. Rep OpenMessageContent x -> OpenMessageContent)
-> Generic OpenMessageContent
forall x. Rep OpenMessageContent x -> OpenMessageContent
forall x. OpenMessageContent -> Rep OpenMessageContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OpenMessageContent x -> OpenMessageContent
$cfrom :: forall x. OpenMessageContent -> Rep OpenMessageContent x
Generic)

-- | Parameter of Function readAllChatMentions
data ReadAllChatMentions
  = -- | Marks all mentions in a chat as read
    ReadAllChatMentions
      { -- | Chat identifier
        ReadAllChatMentions -> Int
chat_id :: I53
      }
  deriving (Int -> ReadAllChatMentions -> ShowS
[ReadAllChatMentions] -> ShowS
ReadAllChatMentions -> String
(Int -> ReadAllChatMentions -> ShowS)
-> (ReadAllChatMentions -> String)
-> ([ReadAllChatMentions] -> ShowS)
-> Show ReadAllChatMentions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadAllChatMentions] -> ShowS
$cshowList :: [ReadAllChatMentions] -> ShowS
show :: ReadAllChatMentions -> String
$cshow :: ReadAllChatMentions -> String
showsPrec :: Int -> ReadAllChatMentions -> ShowS
$cshowsPrec :: Int -> ReadAllChatMentions -> ShowS
Show, ReadAllChatMentions -> ReadAllChatMentions -> Bool
(ReadAllChatMentions -> ReadAllChatMentions -> Bool)
-> (ReadAllChatMentions -> ReadAllChatMentions -> Bool)
-> Eq ReadAllChatMentions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadAllChatMentions -> ReadAllChatMentions -> Bool
$c/= :: ReadAllChatMentions -> ReadAllChatMentions -> Bool
== :: ReadAllChatMentions -> ReadAllChatMentions -> Bool
$c== :: ReadAllChatMentions -> ReadAllChatMentions -> Bool
Eq, (forall x. ReadAllChatMentions -> Rep ReadAllChatMentions x)
-> (forall x. Rep ReadAllChatMentions x -> ReadAllChatMentions)
-> Generic ReadAllChatMentions
forall x. Rep ReadAllChatMentions x -> ReadAllChatMentions
forall x. ReadAllChatMentions -> Rep ReadAllChatMentions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadAllChatMentions x -> ReadAllChatMentions
$cfrom :: forall x. ReadAllChatMentions -> Rep ReadAllChatMentions x
Generic)

-- | Parameter of Function createPrivateChat
data CreatePrivateChat
  = -- | Returns an existing chat corresponding to a given user
    CreatePrivateChat
      { -- | User identifier
        CreatePrivateChat -> Int
user_id :: I32,
        -- | If true, the chat will be created without network request. In this case all information about the chat except its type, title and photo can be incorrect
        CreatePrivateChat -> Bool
force :: Bool
      }
  deriving (Int -> CreatePrivateChat -> ShowS
[CreatePrivateChat] -> ShowS
CreatePrivateChat -> String
(Int -> CreatePrivateChat -> ShowS)
-> (CreatePrivateChat -> String)
-> ([CreatePrivateChat] -> ShowS)
-> Show CreatePrivateChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreatePrivateChat] -> ShowS
$cshowList :: [CreatePrivateChat] -> ShowS
show :: CreatePrivateChat -> String
$cshow :: CreatePrivateChat -> String
showsPrec :: Int -> CreatePrivateChat -> ShowS
$cshowsPrec :: Int -> CreatePrivateChat -> ShowS
Show, CreatePrivateChat -> CreatePrivateChat -> Bool
(CreatePrivateChat -> CreatePrivateChat -> Bool)
-> (CreatePrivateChat -> CreatePrivateChat -> Bool)
-> Eq CreatePrivateChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreatePrivateChat -> CreatePrivateChat -> Bool
$c/= :: CreatePrivateChat -> CreatePrivateChat -> Bool
== :: CreatePrivateChat -> CreatePrivateChat -> Bool
$c== :: CreatePrivateChat -> CreatePrivateChat -> Bool
Eq, (forall x. CreatePrivateChat -> Rep CreatePrivateChat x)
-> (forall x. Rep CreatePrivateChat x -> CreatePrivateChat)
-> Generic CreatePrivateChat
forall x. Rep CreatePrivateChat x -> CreatePrivateChat
forall x. CreatePrivateChat -> Rep CreatePrivateChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreatePrivateChat x -> CreatePrivateChat
$cfrom :: forall x. CreatePrivateChat -> Rep CreatePrivateChat x
Generic)

-- | Parameter of Function createBasicGroupChat
data CreateBasicGroupChat
  = -- | Returns an existing chat corresponding to a known basic group
    CreateBasicGroupChat
      { -- | Basic group identifier
        CreateBasicGroupChat -> Int
basic_group_id :: I32,
        -- | If true, the chat will be created without network request. In this case all information about the chat except its type, title and photo can be incorrect
        CreateBasicGroupChat -> Bool
force :: Bool
      }
  deriving (Int -> CreateBasicGroupChat -> ShowS
[CreateBasicGroupChat] -> ShowS
CreateBasicGroupChat -> String
(Int -> CreateBasicGroupChat -> ShowS)
-> (CreateBasicGroupChat -> String)
-> ([CreateBasicGroupChat] -> ShowS)
-> Show CreateBasicGroupChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateBasicGroupChat] -> ShowS
$cshowList :: [CreateBasicGroupChat] -> ShowS
show :: CreateBasicGroupChat -> String
$cshow :: CreateBasicGroupChat -> String
showsPrec :: Int -> CreateBasicGroupChat -> ShowS
$cshowsPrec :: Int -> CreateBasicGroupChat -> ShowS
Show, CreateBasicGroupChat -> CreateBasicGroupChat -> Bool
(CreateBasicGroupChat -> CreateBasicGroupChat -> Bool)
-> (CreateBasicGroupChat -> CreateBasicGroupChat -> Bool)
-> Eq CreateBasicGroupChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateBasicGroupChat -> CreateBasicGroupChat -> Bool
$c/= :: CreateBasicGroupChat -> CreateBasicGroupChat -> Bool
== :: CreateBasicGroupChat -> CreateBasicGroupChat -> Bool
$c== :: CreateBasicGroupChat -> CreateBasicGroupChat -> Bool
Eq, (forall x. CreateBasicGroupChat -> Rep CreateBasicGroupChat x)
-> (forall x. Rep CreateBasicGroupChat x -> CreateBasicGroupChat)
-> Generic CreateBasicGroupChat
forall x. Rep CreateBasicGroupChat x -> CreateBasicGroupChat
forall x. CreateBasicGroupChat -> Rep CreateBasicGroupChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateBasicGroupChat x -> CreateBasicGroupChat
$cfrom :: forall x. CreateBasicGroupChat -> Rep CreateBasicGroupChat x
Generic)

-- | Parameter of Function createSupergroupChat
data CreateSupergroupChat
  = -- | Returns an existing chat corresponding to a known supergroup or channel
    CreateSupergroupChat
      { -- | Supergroup or channel identifier
        CreateSupergroupChat -> Int
supergroup_id :: I32,
        -- | If true, the chat will be created without network request. In this case all information about the chat except its type, title and photo can be incorrect
        CreateSupergroupChat -> Bool
force :: Bool
      }
  deriving (Int -> CreateSupergroupChat -> ShowS
[CreateSupergroupChat] -> ShowS
CreateSupergroupChat -> String
(Int -> CreateSupergroupChat -> ShowS)
-> (CreateSupergroupChat -> String)
-> ([CreateSupergroupChat] -> ShowS)
-> Show CreateSupergroupChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSupergroupChat] -> ShowS
$cshowList :: [CreateSupergroupChat] -> ShowS
show :: CreateSupergroupChat -> String
$cshow :: CreateSupergroupChat -> String
showsPrec :: Int -> CreateSupergroupChat -> ShowS
$cshowsPrec :: Int -> CreateSupergroupChat -> ShowS
Show, CreateSupergroupChat -> CreateSupergroupChat -> Bool
(CreateSupergroupChat -> CreateSupergroupChat -> Bool)
-> (CreateSupergroupChat -> CreateSupergroupChat -> Bool)
-> Eq CreateSupergroupChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSupergroupChat -> CreateSupergroupChat -> Bool
$c/= :: CreateSupergroupChat -> CreateSupergroupChat -> Bool
== :: CreateSupergroupChat -> CreateSupergroupChat -> Bool
$c== :: CreateSupergroupChat -> CreateSupergroupChat -> Bool
Eq, (forall x. CreateSupergroupChat -> Rep CreateSupergroupChat x)
-> (forall x. Rep CreateSupergroupChat x -> CreateSupergroupChat)
-> Generic CreateSupergroupChat
forall x. Rep CreateSupergroupChat x -> CreateSupergroupChat
forall x. CreateSupergroupChat -> Rep CreateSupergroupChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSupergroupChat x -> CreateSupergroupChat
$cfrom :: forall x. CreateSupergroupChat -> Rep CreateSupergroupChat x
Generic)

-- | Parameter of Function createSecretChat
data CreateSecretChat
  = -- | Returns an existing chat corresponding to a known secret chat
    CreateSecretChat
      { -- | Secret chat identifier
        CreateSecretChat -> Int
secret_chat_id :: I32
      }
  deriving (Int -> CreateSecretChat -> ShowS
[CreateSecretChat] -> ShowS
CreateSecretChat -> String
(Int -> CreateSecretChat -> ShowS)
-> (CreateSecretChat -> String)
-> ([CreateSecretChat] -> ShowS)
-> Show CreateSecretChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateSecretChat] -> ShowS
$cshowList :: [CreateSecretChat] -> ShowS
show :: CreateSecretChat -> String
$cshow :: CreateSecretChat -> String
showsPrec :: Int -> CreateSecretChat -> ShowS
$cshowsPrec :: Int -> CreateSecretChat -> ShowS
Show, CreateSecretChat -> CreateSecretChat -> Bool
(CreateSecretChat -> CreateSecretChat -> Bool)
-> (CreateSecretChat -> CreateSecretChat -> Bool)
-> Eq CreateSecretChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateSecretChat -> CreateSecretChat -> Bool
$c/= :: CreateSecretChat -> CreateSecretChat -> Bool
== :: CreateSecretChat -> CreateSecretChat -> Bool
$c== :: CreateSecretChat -> CreateSecretChat -> Bool
Eq, (forall x. CreateSecretChat -> Rep CreateSecretChat x)
-> (forall x. Rep CreateSecretChat x -> CreateSecretChat)
-> Generic CreateSecretChat
forall x. Rep CreateSecretChat x -> CreateSecretChat
forall x. CreateSecretChat -> Rep CreateSecretChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateSecretChat x -> CreateSecretChat
$cfrom :: forall x. CreateSecretChat -> Rep CreateSecretChat x
Generic)

-- | Parameter of Function createNewBasicGroupChat
data CreateNewBasicGroupChat
  = -- | Creates a new basic group and sends a corresponding messageBasicGroupChatCreate. Returns the newly created chat
    CreateNewBasicGroupChat
      { -- | Identifiers of users to be added to the basic group
        CreateNewBasicGroupChat -> [Int]
user_ids :: ([]) (I32),
        -- | Title of the new basic group; 1-128 characters
        CreateNewBasicGroupChat -> T
title :: T
      }
  deriving (Int -> CreateNewBasicGroupChat -> ShowS
[CreateNewBasicGroupChat] -> ShowS
CreateNewBasicGroupChat -> String
(Int -> CreateNewBasicGroupChat -> ShowS)
-> (CreateNewBasicGroupChat -> String)
-> ([CreateNewBasicGroupChat] -> ShowS)
-> Show CreateNewBasicGroupChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNewBasicGroupChat] -> ShowS
$cshowList :: [CreateNewBasicGroupChat] -> ShowS
show :: CreateNewBasicGroupChat -> String
$cshow :: CreateNewBasicGroupChat -> String
showsPrec :: Int -> CreateNewBasicGroupChat -> ShowS
$cshowsPrec :: Int -> CreateNewBasicGroupChat -> ShowS
Show, CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool
(CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool)
-> (CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool)
-> Eq CreateNewBasicGroupChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool
$c/= :: CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool
== :: CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool
$c== :: CreateNewBasicGroupChat -> CreateNewBasicGroupChat -> Bool
Eq, (forall x.
 CreateNewBasicGroupChat -> Rep CreateNewBasicGroupChat x)
-> (forall x.
    Rep CreateNewBasicGroupChat x -> CreateNewBasicGroupChat)
-> Generic CreateNewBasicGroupChat
forall x. Rep CreateNewBasicGroupChat x -> CreateNewBasicGroupChat
forall x. CreateNewBasicGroupChat -> Rep CreateNewBasicGroupChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNewBasicGroupChat x -> CreateNewBasicGroupChat
$cfrom :: forall x. CreateNewBasicGroupChat -> Rep CreateNewBasicGroupChat x
Generic)

-- | Parameter of Function createNewSupergroupChat
data CreateNewSupergroupChat
  = -- | Creates a new supergroup or channel and sends a corresponding messageSupergroupChatCreate. Returns the newly created chat
    CreateNewSupergroupChat
      { -- | Title of the new chat; 1-128 characters
        CreateNewSupergroupChat -> T
title :: T,
        -- | True, if a channel chat should be created
        CreateNewSupergroupChat -> Bool
is_channel :: Bool,
        -- | Creates a new supergroup or channel and sends a corresponding messageSupergroupChatCreate. Returns the newly created chat
        CreateNewSupergroupChat -> T
description :: T,
        -- | Chat location if a location-based supergroup is being created
        CreateNewSupergroupChat -> ChatLocation
location :: ChatLocation
      }
  deriving (Int -> CreateNewSupergroupChat -> ShowS
[CreateNewSupergroupChat] -> ShowS
CreateNewSupergroupChat -> String
(Int -> CreateNewSupergroupChat -> ShowS)
-> (CreateNewSupergroupChat -> String)
-> ([CreateNewSupergroupChat] -> ShowS)
-> Show CreateNewSupergroupChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNewSupergroupChat] -> ShowS
$cshowList :: [CreateNewSupergroupChat] -> ShowS
show :: CreateNewSupergroupChat -> String
$cshow :: CreateNewSupergroupChat -> String
showsPrec :: Int -> CreateNewSupergroupChat -> ShowS
$cshowsPrec :: Int -> CreateNewSupergroupChat -> ShowS
Show, CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool
(CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool)
-> (CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool)
-> Eq CreateNewSupergroupChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool
$c/= :: CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool
== :: CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool
$c== :: CreateNewSupergroupChat -> CreateNewSupergroupChat -> Bool
Eq, (forall x.
 CreateNewSupergroupChat -> Rep CreateNewSupergroupChat x)
-> (forall x.
    Rep CreateNewSupergroupChat x -> CreateNewSupergroupChat)
-> Generic CreateNewSupergroupChat
forall x. Rep CreateNewSupergroupChat x -> CreateNewSupergroupChat
forall x. CreateNewSupergroupChat -> Rep CreateNewSupergroupChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNewSupergroupChat x -> CreateNewSupergroupChat
$cfrom :: forall x. CreateNewSupergroupChat -> Rep CreateNewSupergroupChat x
Generic)

-- | Parameter of Function createNewSecretChat
data CreateNewSecretChat
  = -- | Creates a new secret chat. Returns the newly created chat
    CreateNewSecretChat
      { -- | Identifier of the target user
        CreateNewSecretChat -> Int
user_id :: I32
      }
  deriving (Int -> CreateNewSecretChat -> ShowS
[CreateNewSecretChat] -> ShowS
CreateNewSecretChat -> String
(Int -> CreateNewSecretChat -> ShowS)
-> (CreateNewSecretChat -> String)
-> ([CreateNewSecretChat] -> ShowS)
-> Show CreateNewSecretChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNewSecretChat] -> ShowS
$cshowList :: [CreateNewSecretChat] -> ShowS
show :: CreateNewSecretChat -> String
$cshow :: CreateNewSecretChat -> String
showsPrec :: Int -> CreateNewSecretChat -> ShowS
$cshowsPrec :: Int -> CreateNewSecretChat -> ShowS
Show, CreateNewSecretChat -> CreateNewSecretChat -> Bool
(CreateNewSecretChat -> CreateNewSecretChat -> Bool)
-> (CreateNewSecretChat -> CreateNewSecretChat -> Bool)
-> Eq CreateNewSecretChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNewSecretChat -> CreateNewSecretChat -> Bool
$c/= :: CreateNewSecretChat -> CreateNewSecretChat -> Bool
== :: CreateNewSecretChat -> CreateNewSecretChat -> Bool
$c== :: CreateNewSecretChat -> CreateNewSecretChat -> Bool
Eq, (forall x. CreateNewSecretChat -> Rep CreateNewSecretChat x)
-> (forall x. Rep CreateNewSecretChat x -> CreateNewSecretChat)
-> Generic CreateNewSecretChat
forall x. Rep CreateNewSecretChat x -> CreateNewSecretChat
forall x. CreateNewSecretChat -> Rep CreateNewSecretChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNewSecretChat x -> CreateNewSecretChat
$cfrom :: forall x. CreateNewSecretChat -> Rep CreateNewSecretChat x
Generic)

-- | Parameter of Function upgradeBasicGroupChatToSupergroupChat
data UpgradeBasicGroupChatToSupergroupChat
  = -- | Creates a new supergroup from an existing basic group and sends a corresponding messageChatUpgradeTo and messageChatUpgradeFrom; requires creator privileges. Deactivates the original basic group
    UpgradeBasicGroupChatToSupergroupChat
      { -- | Identifier of the chat to upgrade
        UpgradeBasicGroupChatToSupergroupChat -> Int
chat_id :: I53
      }
  deriving (Int -> UpgradeBasicGroupChatToSupergroupChat -> ShowS
[UpgradeBasicGroupChatToSupergroupChat] -> ShowS
UpgradeBasicGroupChatToSupergroupChat -> String
(Int -> UpgradeBasicGroupChatToSupergroupChat -> ShowS)
-> (UpgradeBasicGroupChatToSupergroupChat -> String)
-> ([UpgradeBasicGroupChatToSupergroupChat] -> ShowS)
-> Show UpgradeBasicGroupChatToSupergroupChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpgradeBasicGroupChatToSupergroupChat] -> ShowS
$cshowList :: [UpgradeBasicGroupChatToSupergroupChat] -> ShowS
show :: UpgradeBasicGroupChatToSupergroupChat -> String
$cshow :: UpgradeBasicGroupChatToSupergroupChat -> String
showsPrec :: Int -> UpgradeBasicGroupChatToSupergroupChat -> ShowS
$cshowsPrec :: Int -> UpgradeBasicGroupChatToSupergroupChat -> ShowS
Show, UpgradeBasicGroupChatToSupergroupChat
-> UpgradeBasicGroupChatToSupergroupChat -> Bool
(UpgradeBasicGroupChatToSupergroupChat
 -> UpgradeBasicGroupChatToSupergroupChat -> Bool)
-> (UpgradeBasicGroupChatToSupergroupChat
    -> UpgradeBasicGroupChatToSupergroupChat -> Bool)
-> Eq UpgradeBasicGroupChatToSupergroupChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpgradeBasicGroupChatToSupergroupChat
-> UpgradeBasicGroupChatToSupergroupChat -> Bool
$c/= :: UpgradeBasicGroupChatToSupergroupChat
-> UpgradeBasicGroupChatToSupergroupChat -> Bool
== :: UpgradeBasicGroupChatToSupergroupChat
-> UpgradeBasicGroupChatToSupergroupChat -> Bool
$c== :: UpgradeBasicGroupChatToSupergroupChat
-> UpgradeBasicGroupChatToSupergroupChat -> Bool
Eq, (forall x.
 UpgradeBasicGroupChatToSupergroupChat
 -> Rep UpgradeBasicGroupChatToSupergroupChat x)
-> (forall x.
    Rep UpgradeBasicGroupChatToSupergroupChat x
    -> UpgradeBasicGroupChatToSupergroupChat)
-> Generic UpgradeBasicGroupChatToSupergroupChat
forall x.
Rep UpgradeBasicGroupChatToSupergroupChat x
-> UpgradeBasicGroupChatToSupergroupChat
forall x.
UpgradeBasicGroupChatToSupergroupChat
-> Rep UpgradeBasicGroupChatToSupergroupChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpgradeBasicGroupChatToSupergroupChat x
-> UpgradeBasicGroupChatToSupergroupChat
$cfrom :: forall x.
UpgradeBasicGroupChatToSupergroupChat
-> Rep UpgradeBasicGroupChatToSupergroupChat x
Generic)

-- | Parameter of Function setChatChatList
data SetChatChatList
  = -- | Moves a chat to a different chat list. Current chat list of the chat must ne non-null
    SetChatChatList
      { -- | Chat identifier
        SetChatChatList -> Int
chat_id :: I53,
        -- | New chat list of the chat. The chat with the current user (Saved Messages) and the chat 777000 (Telegram) can't be moved to the Archive chat list
        SetChatChatList -> ChatList
chat_list :: ChatList
      }
  deriving (Int -> SetChatChatList -> ShowS
[SetChatChatList] -> ShowS
SetChatChatList -> String
(Int -> SetChatChatList -> ShowS)
-> (SetChatChatList -> String)
-> ([SetChatChatList] -> ShowS)
-> Show SetChatChatList
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatChatList] -> ShowS
$cshowList :: [SetChatChatList] -> ShowS
show :: SetChatChatList -> String
$cshow :: SetChatChatList -> String
showsPrec :: Int -> SetChatChatList -> ShowS
$cshowsPrec :: Int -> SetChatChatList -> ShowS
Show, SetChatChatList -> SetChatChatList -> Bool
(SetChatChatList -> SetChatChatList -> Bool)
-> (SetChatChatList -> SetChatChatList -> Bool)
-> Eq SetChatChatList
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatChatList -> SetChatChatList -> Bool
$c/= :: SetChatChatList -> SetChatChatList -> Bool
== :: SetChatChatList -> SetChatChatList -> Bool
$c== :: SetChatChatList -> SetChatChatList -> Bool
Eq, (forall x. SetChatChatList -> Rep SetChatChatList x)
-> (forall x. Rep SetChatChatList x -> SetChatChatList)
-> Generic SetChatChatList
forall x. Rep SetChatChatList x -> SetChatChatList
forall x. SetChatChatList -> Rep SetChatChatList x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatChatList x -> SetChatChatList
$cfrom :: forall x. SetChatChatList -> Rep SetChatChatList x
Generic)

-- | Parameter of Function setChatTitle
data SetChatTitle
  = -- | Changes the chat title. Supported only for basic groups, supergroups and channels. Requires can_change_info rights. The title will not be changed until the request to the server has been completed
    SetChatTitle
      { -- | Chat identifier
        SetChatTitle -> Int
chat_id :: I53,
        -- | New title of the chat; 1-128 characters
        SetChatTitle -> T
title :: T
      }
  deriving (Int -> SetChatTitle -> ShowS
[SetChatTitle] -> ShowS
SetChatTitle -> String
(Int -> SetChatTitle -> ShowS)
-> (SetChatTitle -> String)
-> ([SetChatTitle] -> ShowS)
-> Show SetChatTitle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatTitle] -> ShowS
$cshowList :: [SetChatTitle] -> ShowS
show :: SetChatTitle -> String
$cshow :: SetChatTitle -> String
showsPrec :: Int -> SetChatTitle -> ShowS
$cshowsPrec :: Int -> SetChatTitle -> ShowS
Show, SetChatTitle -> SetChatTitle -> Bool
(SetChatTitle -> SetChatTitle -> Bool)
-> (SetChatTitle -> SetChatTitle -> Bool) -> Eq SetChatTitle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatTitle -> SetChatTitle -> Bool
$c/= :: SetChatTitle -> SetChatTitle -> Bool
== :: SetChatTitle -> SetChatTitle -> Bool
$c== :: SetChatTitle -> SetChatTitle -> Bool
Eq, (forall x. SetChatTitle -> Rep SetChatTitle x)
-> (forall x. Rep SetChatTitle x -> SetChatTitle)
-> Generic SetChatTitle
forall x. Rep SetChatTitle x -> SetChatTitle
forall x. SetChatTitle -> Rep SetChatTitle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatTitle x -> SetChatTitle
$cfrom :: forall x. SetChatTitle -> Rep SetChatTitle x
Generic)

-- | Parameter of Function setChatPhoto
data SetChatPhoto
  = -- | Changes the photo of a chat. Supported only for basic groups, supergroups and channels. Requires can_change_info rights. The photo will not be changed before request to the server has been completed
    SetChatPhoto
      { -- | Chat identifier
        SetChatPhoto -> Int
chat_id :: I53,
        -- | New chat photo. You can use a zero InputFileId to delete the chat photo. Files that are accessible only by HTTP URL are not acceptable
        SetChatPhoto -> InputFile
photo :: InputFile
      }
  deriving (Int -> SetChatPhoto -> ShowS
[SetChatPhoto] -> ShowS
SetChatPhoto -> String
(Int -> SetChatPhoto -> ShowS)
-> (SetChatPhoto -> String)
-> ([SetChatPhoto] -> ShowS)
-> Show SetChatPhoto
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatPhoto] -> ShowS
$cshowList :: [SetChatPhoto] -> ShowS
show :: SetChatPhoto -> String
$cshow :: SetChatPhoto -> String
showsPrec :: Int -> SetChatPhoto -> ShowS
$cshowsPrec :: Int -> SetChatPhoto -> ShowS
Show, SetChatPhoto -> SetChatPhoto -> Bool
(SetChatPhoto -> SetChatPhoto -> Bool)
-> (SetChatPhoto -> SetChatPhoto -> Bool) -> Eq SetChatPhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatPhoto -> SetChatPhoto -> Bool
$c/= :: SetChatPhoto -> SetChatPhoto -> Bool
== :: SetChatPhoto -> SetChatPhoto -> Bool
$c== :: SetChatPhoto -> SetChatPhoto -> Bool
Eq, (forall x. SetChatPhoto -> Rep SetChatPhoto x)
-> (forall x. Rep SetChatPhoto x -> SetChatPhoto)
-> Generic SetChatPhoto
forall x. Rep SetChatPhoto x -> SetChatPhoto
forall x. SetChatPhoto -> Rep SetChatPhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatPhoto x -> SetChatPhoto
$cfrom :: forall x. SetChatPhoto -> Rep SetChatPhoto x
Generic)

-- | Parameter of Function setChatPermissions
data SetChatPermissions
  = -- | Changes the chat members permissions. Supported only for basic groups and supergroups. Requires can_restrict_members administrator right
    SetChatPermissions
      { -- | Chat identifier
        SetChatPermissions -> Int
chat_id :: I53,
        -- | New non-administrator members permissions in the chat
        SetChatPermissions -> ChatPermissions
permissions :: ChatPermissions
      }
  deriving (Int -> SetChatPermissions -> ShowS
[SetChatPermissions] -> ShowS
SetChatPermissions -> String
(Int -> SetChatPermissions -> ShowS)
-> (SetChatPermissions -> String)
-> ([SetChatPermissions] -> ShowS)
-> Show SetChatPermissions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatPermissions] -> ShowS
$cshowList :: [SetChatPermissions] -> ShowS
show :: SetChatPermissions -> String
$cshow :: SetChatPermissions -> String
showsPrec :: Int -> SetChatPermissions -> ShowS
$cshowsPrec :: Int -> SetChatPermissions -> ShowS
Show, SetChatPermissions -> SetChatPermissions -> Bool
(SetChatPermissions -> SetChatPermissions -> Bool)
-> (SetChatPermissions -> SetChatPermissions -> Bool)
-> Eq SetChatPermissions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatPermissions -> SetChatPermissions -> Bool
$c/= :: SetChatPermissions -> SetChatPermissions -> Bool
== :: SetChatPermissions -> SetChatPermissions -> Bool
$c== :: SetChatPermissions -> SetChatPermissions -> Bool
Eq, (forall x. SetChatPermissions -> Rep SetChatPermissions x)
-> (forall x. Rep SetChatPermissions x -> SetChatPermissions)
-> Generic SetChatPermissions
forall x. Rep SetChatPermissions x -> SetChatPermissions
forall x. SetChatPermissions -> Rep SetChatPermissions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatPermissions x -> SetChatPermissions
$cfrom :: forall x. SetChatPermissions -> Rep SetChatPermissions x
Generic)

-- | Parameter of Function setChatDraftMessage
data SetChatDraftMessage
  = -- | Changes the draft message in a chat
    SetChatDraftMessage
      { -- | Chat identifier
        SetChatDraftMessage -> Int
chat_id :: I53,
        -- | New draft message; may be null
        SetChatDraftMessage -> DraftMessage
draft_message :: DraftMessage
      }
  deriving (Int -> SetChatDraftMessage -> ShowS
[SetChatDraftMessage] -> ShowS
SetChatDraftMessage -> String
(Int -> SetChatDraftMessage -> ShowS)
-> (SetChatDraftMessage -> String)
-> ([SetChatDraftMessage] -> ShowS)
-> Show SetChatDraftMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatDraftMessage] -> ShowS
$cshowList :: [SetChatDraftMessage] -> ShowS
show :: SetChatDraftMessage -> String
$cshow :: SetChatDraftMessage -> String
showsPrec :: Int -> SetChatDraftMessage -> ShowS
$cshowsPrec :: Int -> SetChatDraftMessage -> ShowS
Show, SetChatDraftMessage -> SetChatDraftMessage -> Bool
(SetChatDraftMessage -> SetChatDraftMessage -> Bool)
-> (SetChatDraftMessage -> SetChatDraftMessage -> Bool)
-> Eq SetChatDraftMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatDraftMessage -> SetChatDraftMessage -> Bool
$c/= :: SetChatDraftMessage -> SetChatDraftMessage -> Bool
== :: SetChatDraftMessage -> SetChatDraftMessage -> Bool
$c== :: SetChatDraftMessage -> SetChatDraftMessage -> Bool
Eq, (forall x. SetChatDraftMessage -> Rep SetChatDraftMessage x)
-> (forall x. Rep SetChatDraftMessage x -> SetChatDraftMessage)
-> Generic SetChatDraftMessage
forall x. Rep SetChatDraftMessage x -> SetChatDraftMessage
forall x. SetChatDraftMessage -> Rep SetChatDraftMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatDraftMessage x -> SetChatDraftMessage
$cfrom :: forall x. SetChatDraftMessage -> Rep SetChatDraftMessage x
Generic)

-- | Parameter of Function setChatNotificationSettings
data SetChatNotificationSettings
  = -- | Changes the notification settings of a chat. Notification settings of a chat with the current user (Saved Messages) can't be changed
    SetChatNotificationSettings
      { -- | Chat identifier
        SetChatNotificationSettings -> Int
chat_id :: I53,
        -- | New notification settings for the chat. If the chat is muted for more than 1 week, it is considered to be muted forever
        SetChatNotificationSettings -> ChatNotificationSettings
notification_settings :: ChatNotificationSettings
      }
  deriving (Int -> SetChatNotificationSettings -> ShowS
[SetChatNotificationSettings] -> ShowS
SetChatNotificationSettings -> String
(Int -> SetChatNotificationSettings -> ShowS)
-> (SetChatNotificationSettings -> String)
-> ([SetChatNotificationSettings] -> ShowS)
-> Show SetChatNotificationSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatNotificationSettings] -> ShowS
$cshowList :: [SetChatNotificationSettings] -> ShowS
show :: SetChatNotificationSettings -> String
$cshow :: SetChatNotificationSettings -> String
showsPrec :: Int -> SetChatNotificationSettings -> ShowS
$cshowsPrec :: Int -> SetChatNotificationSettings -> ShowS
Show, SetChatNotificationSettings -> SetChatNotificationSettings -> Bool
(SetChatNotificationSettings
 -> SetChatNotificationSettings -> Bool)
-> (SetChatNotificationSettings
    -> SetChatNotificationSettings -> Bool)
-> Eq SetChatNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatNotificationSettings -> SetChatNotificationSettings -> Bool
$c/= :: SetChatNotificationSettings -> SetChatNotificationSettings -> Bool
== :: SetChatNotificationSettings -> SetChatNotificationSettings -> Bool
$c== :: SetChatNotificationSettings -> SetChatNotificationSettings -> Bool
Eq, (forall x.
 SetChatNotificationSettings -> Rep SetChatNotificationSettings x)
-> (forall x.
    Rep SetChatNotificationSettings x -> SetChatNotificationSettings)
-> Generic SetChatNotificationSettings
forall x.
Rep SetChatNotificationSettings x -> SetChatNotificationSettings
forall x.
SetChatNotificationSettings -> Rep SetChatNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetChatNotificationSettings x -> SetChatNotificationSettings
$cfrom :: forall x.
SetChatNotificationSettings -> Rep SetChatNotificationSettings x
Generic)

-- | Parameter of Function toggleChatIsPinned
data ToggleChatIsPinned
  = -- | Changes the pinned state of a chat. You can pin up to GetOption("pinned_chat_count_max")/GetOption("pinned_archived_chat_count_max") non-secret chats and the same number of secret chats in the main/archive chat list
    ToggleChatIsPinned
      { -- | Chat identifier
        ToggleChatIsPinned -> Int
chat_id :: I53,
        -- | New value of is_pinned
        ToggleChatIsPinned -> Bool
is_pinned :: Bool
      }
  deriving (Int -> ToggleChatIsPinned -> ShowS
[ToggleChatIsPinned] -> ShowS
ToggleChatIsPinned -> String
(Int -> ToggleChatIsPinned -> ShowS)
-> (ToggleChatIsPinned -> String)
-> ([ToggleChatIsPinned] -> ShowS)
-> Show ToggleChatIsPinned
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToggleChatIsPinned] -> ShowS
$cshowList :: [ToggleChatIsPinned] -> ShowS
show :: ToggleChatIsPinned -> String
$cshow :: ToggleChatIsPinned -> String
showsPrec :: Int -> ToggleChatIsPinned -> ShowS
$cshowsPrec :: Int -> ToggleChatIsPinned -> ShowS
Show, ToggleChatIsPinned -> ToggleChatIsPinned -> Bool
(ToggleChatIsPinned -> ToggleChatIsPinned -> Bool)
-> (ToggleChatIsPinned -> ToggleChatIsPinned -> Bool)
-> Eq ToggleChatIsPinned
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToggleChatIsPinned -> ToggleChatIsPinned -> Bool
$c/= :: ToggleChatIsPinned -> ToggleChatIsPinned -> Bool
== :: ToggleChatIsPinned -> ToggleChatIsPinned -> Bool
$c== :: ToggleChatIsPinned -> ToggleChatIsPinned -> Bool
Eq, (forall x. ToggleChatIsPinned -> Rep ToggleChatIsPinned x)
-> (forall x. Rep ToggleChatIsPinned x -> ToggleChatIsPinned)
-> Generic ToggleChatIsPinned
forall x. Rep ToggleChatIsPinned x -> ToggleChatIsPinned
forall x. ToggleChatIsPinned -> Rep ToggleChatIsPinned x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ToggleChatIsPinned x -> ToggleChatIsPinned
$cfrom :: forall x. ToggleChatIsPinned -> Rep ToggleChatIsPinned x
Generic)

-- | Parameter of Function toggleChatIsMarkedAsUnread
data ToggleChatIsMarkedAsUnread
  = -- | Changes the marked as unread state of a chat
    ToggleChatIsMarkedAsUnread
      { -- | Chat identifier
        ToggleChatIsMarkedAsUnread -> Int
chat_id :: I53,
        -- | New value of is_marked_as_unread
        ToggleChatIsMarkedAsUnread -> Bool
is_marked_as_unread :: Bool
      }
  deriving (Int -> ToggleChatIsMarkedAsUnread -> ShowS
[ToggleChatIsMarkedAsUnread] -> ShowS
ToggleChatIsMarkedAsUnread -> String
(Int -> ToggleChatIsMarkedAsUnread -> ShowS)
-> (ToggleChatIsMarkedAsUnread -> String)
-> ([ToggleChatIsMarkedAsUnread] -> ShowS)
-> Show ToggleChatIsMarkedAsUnread
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToggleChatIsMarkedAsUnread] -> ShowS
$cshowList :: [ToggleChatIsMarkedAsUnread] -> ShowS
show :: ToggleChatIsMarkedAsUnread -> String
$cshow :: ToggleChatIsMarkedAsUnread -> String
showsPrec :: Int -> ToggleChatIsMarkedAsUnread -> ShowS
$cshowsPrec :: Int -> ToggleChatIsMarkedAsUnread -> ShowS
Show, ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool
(ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool)
-> (ToggleChatIsMarkedAsUnread
    -> ToggleChatIsMarkedAsUnread -> Bool)
-> Eq ToggleChatIsMarkedAsUnread
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool
$c/= :: ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool
== :: ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool
$c== :: ToggleChatIsMarkedAsUnread -> ToggleChatIsMarkedAsUnread -> Bool
Eq, (forall x.
 ToggleChatIsMarkedAsUnread -> Rep ToggleChatIsMarkedAsUnread x)
-> (forall x.
    Rep ToggleChatIsMarkedAsUnread x -> ToggleChatIsMarkedAsUnread)
-> Generic ToggleChatIsMarkedAsUnread
forall x.
Rep ToggleChatIsMarkedAsUnread x -> ToggleChatIsMarkedAsUnread
forall x.
ToggleChatIsMarkedAsUnread -> Rep ToggleChatIsMarkedAsUnread x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ToggleChatIsMarkedAsUnread x -> ToggleChatIsMarkedAsUnread
$cfrom :: forall x.
ToggleChatIsMarkedAsUnread -> Rep ToggleChatIsMarkedAsUnread x
Generic)

-- | Parameter of Function toggleChatDefaultDisableNotification
data ToggleChatDefaultDisableNotification
  = -- | Changes the value of the default disable_notification parameter, used when a message is sent to a chat
    ToggleChatDefaultDisableNotification
      { -- | Chat identifier
        ToggleChatDefaultDisableNotification -> Int
chat_id :: I53,
        -- | New value of default_disable_notification
        ToggleChatDefaultDisableNotification -> Bool
default_disable_notification :: Bool
      }
  deriving (Int -> ToggleChatDefaultDisableNotification -> ShowS
[ToggleChatDefaultDisableNotification] -> ShowS
ToggleChatDefaultDisableNotification -> String
(Int -> ToggleChatDefaultDisableNotification -> ShowS)
-> (ToggleChatDefaultDisableNotification -> String)
-> ([ToggleChatDefaultDisableNotification] -> ShowS)
-> Show ToggleChatDefaultDisableNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToggleChatDefaultDisableNotification] -> ShowS
$cshowList :: [ToggleChatDefaultDisableNotification] -> ShowS
show :: ToggleChatDefaultDisableNotification -> String
$cshow :: ToggleChatDefaultDisableNotification -> String
showsPrec :: Int -> ToggleChatDefaultDisableNotification -> ShowS
$cshowsPrec :: Int -> ToggleChatDefaultDisableNotification -> ShowS
Show, ToggleChatDefaultDisableNotification
-> ToggleChatDefaultDisableNotification -> Bool
(ToggleChatDefaultDisableNotification
 -> ToggleChatDefaultDisableNotification -> Bool)
-> (ToggleChatDefaultDisableNotification
    -> ToggleChatDefaultDisableNotification -> Bool)
-> Eq ToggleChatDefaultDisableNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToggleChatDefaultDisableNotification
-> ToggleChatDefaultDisableNotification -> Bool
$c/= :: ToggleChatDefaultDisableNotification
-> ToggleChatDefaultDisableNotification -> Bool
== :: ToggleChatDefaultDisableNotification
-> ToggleChatDefaultDisableNotification -> Bool
$c== :: ToggleChatDefaultDisableNotification
-> ToggleChatDefaultDisableNotification -> Bool
Eq, (forall x.
 ToggleChatDefaultDisableNotification
 -> Rep ToggleChatDefaultDisableNotification x)
-> (forall x.
    Rep ToggleChatDefaultDisableNotification x
    -> ToggleChatDefaultDisableNotification)
-> Generic ToggleChatDefaultDisableNotification
forall x.
Rep ToggleChatDefaultDisableNotification x
-> ToggleChatDefaultDisableNotification
forall x.
ToggleChatDefaultDisableNotification
-> Rep ToggleChatDefaultDisableNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ToggleChatDefaultDisableNotification x
-> ToggleChatDefaultDisableNotification
$cfrom :: forall x.
ToggleChatDefaultDisableNotification
-> Rep ToggleChatDefaultDisableNotification x
Generic)

-- | Parameter of Function setChatClientData
data SetChatClientData
  = -- | Changes client data associated with a chat
    SetChatClientData
      { -- | Chat identifier
        SetChatClientData -> Int
chat_id :: I53,
        -- | New value of client_data
        SetChatClientData -> T
client_data :: T
      }
  deriving (Int -> SetChatClientData -> ShowS
[SetChatClientData] -> ShowS
SetChatClientData -> String
(Int -> SetChatClientData -> ShowS)
-> (SetChatClientData -> String)
-> ([SetChatClientData] -> ShowS)
-> Show SetChatClientData
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatClientData] -> ShowS
$cshowList :: [SetChatClientData] -> ShowS
show :: SetChatClientData -> String
$cshow :: SetChatClientData -> String
showsPrec :: Int -> SetChatClientData -> ShowS
$cshowsPrec :: Int -> SetChatClientData -> ShowS
Show, SetChatClientData -> SetChatClientData -> Bool
(SetChatClientData -> SetChatClientData -> Bool)
-> (SetChatClientData -> SetChatClientData -> Bool)
-> Eq SetChatClientData
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatClientData -> SetChatClientData -> Bool
$c/= :: SetChatClientData -> SetChatClientData -> Bool
== :: SetChatClientData -> SetChatClientData -> Bool
$c== :: SetChatClientData -> SetChatClientData -> Bool
Eq, (forall x. SetChatClientData -> Rep SetChatClientData x)
-> (forall x. Rep SetChatClientData x -> SetChatClientData)
-> Generic SetChatClientData
forall x. Rep SetChatClientData x -> SetChatClientData
forall x. SetChatClientData -> Rep SetChatClientData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatClientData x -> SetChatClientData
$cfrom :: forall x. SetChatClientData -> Rep SetChatClientData x
Generic)

-- | Parameter of Function setChatDescription
data SetChatDescription
  = -- | Changes information about a chat. Available for basic groups, supergroups, and channels. Requires can_change_info rights
    SetChatDescription
      { -- | Identifier of the chat
        SetChatDescription -> Int
chat_id :: I53,
        -- | Changes information about a chat. Available for basic groups, supergroups, and channels. Requires can_change_info rights
        SetChatDescription -> T
description :: T
      }
  deriving (Int -> SetChatDescription -> ShowS
[SetChatDescription] -> ShowS
SetChatDescription -> String
(Int -> SetChatDescription -> ShowS)
-> (SetChatDescription -> String)
-> ([SetChatDescription] -> ShowS)
-> Show SetChatDescription
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatDescription] -> ShowS
$cshowList :: [SetChatDescription] -> ShowS
show :: SetChatDescription -> String
$cshow :: SetChatDescription -> String
showsPrec :: Int -> SetChatDescription -> ShowS
$cshowsPrec :: Int -> SetChatDescription -> ShowS
Show, SetChatDescription -> SetChatDescription -> Bool
(SetChatDescription -> SetChatDescription -> Bool)
-> (SetChatDescription -> SetChatDescription -> Bool)
-> Eq SetChatDescription
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatDescription -> SetChatDescription -> Bool
$c/= :: SetChatDescription -> SetChatDescription -> Bool
== :: SetChatDescription -> SetChatDescription -> Bool
$c== :: SetChatDescription -> SetChatDescription -> Bool
Eq, (forall x. SetChatDescription -> Rep SetChatDescription x)
-> (forall x. Rep SetChatDescription x -> SetChatDescription)
-> Generic SetChatDescription
forall x. Rep SetChatDescription x -> SetChatDescription
forall x. SetChatDescription -> Rep SetChatDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatDescription x -> SetChatDescription
$cfrom :: forall x. SetChatDescription -> Rep SetChatDescription x
Generic)

-- | Parameter of Function setChatDiscussionGroup
data SetChatDiscussionGroup
  = -- | Changes the discussion group of a channel chat; requires can_change_info rights in the channel if it is specified
    SetChatDiscussionGroup
      { -- | Identifier of the channel chat. Pass 0 to remove a link from the supergroup passed in the second argument to a linked channel chat (requires can_pin_messages rights in the supergroup)
        SetChatDiscussionGroup -> Int
chat_id :: I53,
        -- | Identifier of a new channel's discussion group. Use 0 to remove the discussion group.
        SetChatDiscussionGroup -> Int
discussion_chat_id :: I53
      }
  deriving (Int -> SetChatDiscussionGroup -> ShowS
[SetChatDiscussionGroup] -> ShowS
SetChatDiscussionGroup -> String
(Int -> SetChatDiscussionGroup -> ShowS)
-> (SetChatDiscussionGroup -> String)
-> ([SetChatDiscussionGroup] -> ShowS)
-> Show SetChatDiscussionGroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatDiscussionGroup] -> ShowS
$cshowList :: [SetChatDiscussionGroup] -> ShowS
show :: SetChatDiscussionGroup -> String
$cshow :: SetChatDiscussionGroup -> String
showsPrec :: Int -> SetChatDiscussionGroup -> ShowS
$cshowsPrec :: Int -> SetChatDiscussionGroup -> ShowS
Show, SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool
(SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool)
-> (SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool)
-> Eq SetChatDiscussionGroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool
$c/= :: SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool
== :: SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool
$c== :: SetChatDiscussionGroup -> SetChatDiscussionGroup -> Bool
Eq, (forall x. SetChatDiscussionGroup -> Rep SetChatDiscussionGroup x)
-> (forall x.
    Rep SetChatDiscussionGroup x -> SetChatDiscussionGroup)
-> Generic SetChatDiscussionGroup
forall x. Rep SetChatDiscussionGroup x -> SetChatDiscussionGroup
forall x. SetChatDiscussionGroup -> Rep SetChatDiscussionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatDiscussionGroup x -> SetChatDiscussionGroup
$cfrom :: forall x. SetChatDiscussionGroup -> Rep SetChatDiscussionGroup x
Generic)

-- | Parameter of Function setChatLocation
data SetChatLocation
  = -- | Changes the location of a chat. Available only for some location-based supergroups, use supergroupFullInfo.can_set_location to check whether the method is allowed to use
    SetChatLocation
      { -- | Chat identifier
        SetChatLocation -> Int
chat_id :: I53,
        -- | New location for the chat; must be valid and not null
        SetChatLocation -> ChatLocation
location :: ChatLocation
      }
  deriving (Int -> SetChatLocation -> ShowS
[SetChatLocation] -> ShowS
SetChatLocation -> String
(Int -> SetChatLocation -> ShowS)
-> (SetChatLocation -> String)
-> ([SetChatLocation] -> ShowS)
-> Show SetChatLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatLocation] -> ShowS
$cshowList :: [SetChatLocation] -> ShowS
show :: SetChatLocation -> String
$cshow :: SetChatLocation -> String
showsPrec :: Int -> SetChatLocation -> ShowS
$cshowsPrec :: Int -> SetChatLocation -> ShowS
Show, SetChatLocation -> SetChatLocation -> Bool
(SetChatLocation -> SetChatLocation -> Bool)
-> (SetChatLocation -> SetChatLocation -> Bool)
-> Eq SetChatLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatLocation -> SetChatLocation -> Bool
$c/= :: SetChatLocation -> SetChatLocation -> Bool
== :: SetChatLocation -> SetChatLocation -> Bool
$c== :: SetChatLocation -> SetChatLocation -> Bool
Eq, (forall x. SetChatLocation -> Rep SetChatLocation x)
-> (forall x. Rep SetChatLocation x -> SetChatLocation)
-> Generic SetChatLocation
forall x. Rep SetChatLocation x -> SetChatLocation
forall x. SetChatLocation -> Rep SetChatLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatLocation x -> SetChatLocation
$cfrom :: forall x. SetChatLocation -> Rep SetChatLocation x
Generic)

-- | Parameter of Function setChatSlowModeDelay
data SetChatSlowModeDelay
  = -- | Changes the slow mode delay of a chat. Available only for supergroups; requires can_restrict_members rights
    SetChatSlowModeDelay
      { -- | Chat identifier
        SetChatSlowModeDelay -> Int
chat_id :: I53,
        -- | New slow mode delay for the chat; must be one of 0, 10, 30, 60, 300, 900, 3600
        SetChatSlowModeDelay -> Int
slow_mode_delay :: I32
      }
  deriving (Int -> SetChatSlowModeDelay -> ShowS
[SetChatSlowModeDelay] -> ShowS
SetChatSlowModeDelay -> String
(Int -> SetChatSlowModeDelay -> ShowS)
-> (SetChatSlowModeDelay -> String)
-> ([SetChatSlowModeDelay] -> ShowS)
-> Show SetChatSlowModeDelay
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatSlowModeDelay] -> ShowS
$cshowList :: [SetChatSlowModeDelay] -> ShowS
show :: SetChatSlowModeDelay -> String
$cshow :: SetChatSlowModeDelay -> String
showsPrec :: Int -> SetChatSlowModeDelay -> ShowS
$cshowsPrec :: Int -> SetChatSlowModeDelay -> ShowS
Show, SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool
(SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool)
-> (SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool)
-> Eq SetChatSlowModeDelay
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool
$c/= :: SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool
== :: SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool
$c== :: SetChatSlowModeDelay -> SetChatSlowModeDelay -> Bool
Eq, (forall x. SetChatSlowModeDelay -> Rep SetChatSlowModeDelay x)
-> (forall x. Rep SetChatSlowModeDelay x -> SetChatSlowModeDelay)
-> Generic SetChatSlowModeDelay
forall x. Rep SetChatSlowModeDelay x -> SetChatSlowModeDelay
forall x. SetChatSlowModeDelay -> Rep SetChatSlowModeDelay x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatSlowModeDelay x -> SetChatSlowModeDelay
$cfrom :: forall x. SetChatSlowModeDelay -> Rep SetChatSlowModeDelay x
Generic)

-- | Parameter of Function pinChatMessage
data PinChatMessage
  = -- | Pins a message in a chat; requires can_pin_messages rights
    PinChatMessage
      { -- | Identifier of the chat
        PinChatMessage -> Int
chat_id :: I53,
        -- | Identifier of the new pinned message
        PinChatMessage -> Int
message_id :: I53,
        -- | True, if there should be no notification about the pinned message
        PinChatMessage -> Bool
disable_notification :: Bool
      }
  deriving (Int -> PinChatMessage -> ShowS
[PinChatMessage] -> ShowS
PinChatMessage -> String
(Int -> PinChatMessage -> ShowS)
-> (PinChatMessage -> String)
-> ([PinChatMessage] -> ShowS)
-> Show PinChatMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PinChatMessage] -> ShowS
$cshowList :: [PinChatMessage] -> ShowS
show :: PinChatMessage -> String
$cshow :: PinChatMessage -> String
showsPrec :: Int -> PinChatMessage -> ShowS
$cshowsPrec :: Int -> PinChatMessage -> ShowS
Show, PinChatMessage -> PinChatMessage -> Bool
(PinChatMessage -> PinChatMessage -> Bool)
-> (PinChatMessage -> PinChatMessage -> Bool) -> Eq PinChatMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PinChatMessage -> PinChatMessage -> Bool
$c/= :: PinChatMessage -> PinChatMessage -> Bool
== :: PinChatMessage -> PinChatMessage -> Bool
$c== :: PinChatMessage -> PinChatMessage -> Bool
Eq, (forall x. PinChatMessage -> Rep PinChatMessage x)
-> (forall x. Rep PinChatMessage x -> PinChatMessage)
-> Generic PinChatMessage
forall x. Rep PinChatMessage x -> PinChatMessage
forall x. PinChatMessage -> Rep PinChatMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PinChatMessage x -> PinChatMessage
$cfrom :: forall x. PinChatMessage -> Rep PinChatMessage x
Generic)

-- | Parameter of Function unpinChatMessage
data UnpinChatMessage
  = -- | Removes the pinned message from a chat; requires can_pin_messages rights in the group or channel
    UnpinChatMessage
      { -- | Identifier of the chat
        UnpinChatMessage -> Int
chat_id :: I53
      }
  deriving (Int -> UnpinChatMessage -> ShowS
[UnpinChatMessage] -> ShowS
UnpinChatMessage -> String
(Int -> UnpinChatMessage -> ShowS)
-> (UnpinChatMessage -> String)
-> ([UnpinChatMessage] -> ShowS)
-> Show UnpinChatMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnpinChatMessage] -> ShowS
$cshowList :: [UnpinChatMessage] -> ShowS
show :: UnpinChatMessage -> String
$cshow :: UnpinChatMessage -> String
showsPrec :: Int -> UnpinChatMessage -> ShowS
$cshowsPrec :: Int -> UnpinChatMessage -> ShowS
Show, UnpinChatMessage -> UnpinChatMessage -> Bool
(UnpinChatMessage -> UnpinChatMessage -> Bool)
-> (UnpinChatMessage -> UnpinChatMessage -> Bool)
-> Eq UnpinChatMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnpinChatMessage -> UnpinChatMessage -> Bool
$c/= :: UnpinChatMessage -> UnpinChatMessage -> Bool
== :: UnpinChatMessage -> UnpinChatMessage -> Bool
$c== :: UnpinChatMessage -> UnpinChatMessage -> Bool
Eq, (forall x. UnpinChatMessage -> Rep UnpinChatMessage x)
-> (forall x. Rep UnpinChatMessage x -> UnpinChatMessage)
-> Generic UnpinChatMessage
forall x. Rep UnpinChatMessage x -> UnpinChatMessage
forall x. UnpinChatMessage -> Rep UnpinChatMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnpinChatMessage x -> UnpinChatMessage
$cfrom :: forall x. UnpinChatMessage -> Rep UnpinChatMessage x
Generic)

-- | Parameter of Function joinChat
data JoinChat
  = -- | Adds current user as a new member to a chat. Private and secret chats can't be joined using this method
    JoinChat
      { -- | Chat identifier
        JoinChat -> Int
chat_id :: I53
      }
  deriving (Int -> JoinChat -> ShowS
[JoinChat] -> ShowS
JoinChat -> String
(Int -> JoinChat -> ShowS)
-> (JoinChat -> String) -> ([JoinChat] -> ShowS) -> Show JoinChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinChat] -> ShowS
$cshowList :: [JoinChat] -> ShowS
show :: JoinChat -> String
$cshow :: JoinChat -> String
showsPrec :: Int -> JoinChat -> ShowS
$cshowsPrec :: Int -> JoinChat -> ShowS
Show, JoinChat -> JoinChat -> Bool
(JoinChat -> JoinChat -> Bool)
-> (JoinChat -> JoinChat -> Bool) -> Eq JoinChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinChat -> JoinChat -> Bool
$c/= :: JoinChat -> JoinChat -> Bool
== :: JoinChat -> JoinChat -> Bool
$c== :: JoinChat -> JoinChat -> Bool
Eq, (forall x. JoinChat -> Rep JoinChat x)
-> (forall x. Rep JoinChat x -> JoinChat) -> Generic JoinChat
forall x. Rep JoinChat x -> JoinChat
forall x. JoinChat -> Rep JoinChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinChat x -> JoinChat
$cfrom :: forall x. JoinChat -> Rep JoinChat x
Generic)

-- | Parameter of Function leaveChat
data LeaveChat
  = -- | Removes current user from chat members. Private and secret chats can't be left using this method
    LeaveChat
      { -- | Chat identifier
        LeaveChat -> Int
chat_id :: I53
      }
  deriving (Int -> LeaveChat -> ShowS
[LeaveChat] -> ShowS
LeaveChat -> String
(Int -> LeaveChat -> ShowS)
-> (LeaveChat -> String)
-> ([LeaveChat] -> ShowS)
-> Show LeaveChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LeaveChat] -> ShowS
$cshowList :: [LeaveChat] -> ShowS
show :: LeaveChat -> String
$cshow :: LeaveChat -> String
showsPrec :: Int -> LeaveChat -> ShowS
$cshowsPrec :: Int -> LeaveChat -> ShowS
Show, LeaveChat -> LeaveChat -> Bool
(LeaveChat -> LeaveChat -> Bool)
-> (LeaveChat -> LeaveChat -> Bool) -> Eq LeaveChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeaveChat -> LeaveChat -> Bool
$c/= :: LeaveChat -> LeaveChat -> Bool
== :: LeaveChat -> LeaveChat -> Bool
$c== :: LeaveChat -> LeaveChat -> Bool
Eq, (forall x. LeaveChat -> Rep LeaveChat x)
-> (forall x. Rep LeaveChat x -> LeaveChat) -> Generic LeaveChat
forall x. Rep LeaveChat x -> LeaveChat
forall x. LeaveChat -> Rep LeaveChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LeaveChat x -> LeaveChat
$cfrom :: forall x. LeaveChat -> Rep LeaveChat x
Generic)

-- | Parameter of Function addChatMember
data AddChatMember
  = -- | Adds a new member to a chat. Members can't be added to private or secret chats. Members will not be added until the chat state has been synchronized with the server
    AddChatMember
      { -- | Chat identifier
        AddChatMember -> Int
chat_id :: I53,
        -- | Identifier of the user
        AddChatMember -> Int
user_id :: I32,
        -- | The number of earlier messages from the chat to be forwarded to the new member; up to 100. Ignored for supergroups and channels
        AddChatMember -> Int
forward_limit :: I32
      }
  deriving (Int -> AddChatMember -> ShowS
[AddChatMember] -> ShowS
AddChatMember -> String
(Int -> AddChatMember -> ShowS)
-> (AddChatMember -> String)
-> ([AddChatMember] -> ShowS)
-> Show AddChatMember
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddChatMember] -> ShowS
$cshowList :: [AddChatMember] -> ShowS
show :: AddChatMember -> String
$cshow :: AddChatMember -> String
showsPrec :: Int -> AddChatMember -> ShowS
$cshowsPrec :: Int -> AddChatMember -> ShowS
Show, AddChatMember -> AddChatMember -> Bool
(AddChatMember -> AddChatMember -> Bool)
-> (AddChatMember -> AddChatMember -> Bool) -> Eq AddChatMember
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddChatMember -> AddChatMember -> Bool
$c/= :: AddChatMember -> AddChatMember -> Bool
== :: AddChatMember -> AddChatMember -> Bool
$c== :: AddChatMember -> AddChatMember -> Bool
Eq, (forall x. AddChatMember -> Rep AddChatMember x)
-> (forall x. Rep AddChatMember x -> AddChatMember)
-> Generic AddChatMember
forall x. Rep AddChatMember x -> AddChatMember
forall x. AddChatMember -> Rep AddChatMember x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddChatMember x -> AddChatMember
$cfrom :: forall x. AddChatMember -> Rep AddChatMember x
Generic)

-- | Parameter of Function addChatMembers
data AddChatMembers
  = -- | Adds multiple new members to a chat. Currently this option is only available for supergroups and channels. This option can't be used to join a chat. Members can't be added to a channel if it has more than 200 members. Members will not be added until the chat state has been synchronized with the server
    AddChatMembers
      { -- | Chat identifier
        AddChatMembers -> Int
chat_id :: I53,
        -- | Identifiers of the users to be added to the chat
        AddChatMembers -> [Int]
user_ids :: ([]) (I32)
      }
  deriving (Int -> AddChatMembers -> ShowS
[AddChatMembers] -> ShowS
AddChatMembers -> String
(Int -> AddChatMembers -> ShowS)
-> (AddChatMembers -> String)
-> ([AddChatMembers] -> ShowS)
-> Show AddChatMembers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddChatMembers] -> ShowS
$cshowList :: [AddChatMembers] -> ShowS
show :: AddChatMembers -> String
$cshow :: AddChatMembers -> String
showsPrec :: Int -> AddChatMembers -> ShowS
$cshowsPrec :: Int -> AddChatMembers -> ShowS
Show, AddChatMembers -> AddChatMembers -> Bool
(AddChatMembers -> AddChatMembers -> Bool)
-> (AddChatMembers -> AddChatMembers -> Bool) -> Eq AddChatMembers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddChatMembers -> AddChatMembers -> Bool
$c/= :: AddChatMembers -> AddChatMembers -> Bool
== :: AddChatMembers -> AddChatMembers -> Bool
$c== :: AddChatMembers -> AddChatMembers -> Bool
Eq, (forall x. AddChatMembers -> Rep AddChatMembers x)
-> (forall x. Rep AddChatMembers x -> AddChatMembers)
-> Generic AddChatMembers
forall x. Rep AddChatMembers x -> AddChatMembers
forall x. AddChatMembers -> Rep AddChatMembers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddChatMembers x -> AddChatMembers
$cfrom :: forall x. AddChatMembers -> Rep AddChatMembers x
Generic)

-- | Parameter of Function setChatMemberStatus
data SetChatMemberStatus
  = -- | Changes the status of a chat member, needs appropriate privileges. This function is currently not suitable for adding new members to the chat and transferring chat ownership; instead, use addChatMember or transferChatOwnership. The chat member status will not be changed until it has been synchronized with the server
    SetChatMemberStatus
      { -- | Chat identifier
        SetChatMemberStatus -> Int
chat_id :: I53,
        -- | User identifier
        SetChatMemberStatus -> Int
user_id :: I32,
        -- | The new status of the member in the chat
        SetChatMemberStatus -> ChatMemberStatus
status :: ChatMemberStatus
      }
  deriving (Int -> SetChatMemberStatus -> ShowS
[SetChatMemberStatus] -> ShowS
SetChatMemberStatus -> String
(Int -> SetChatMemberStatus -> ShowS)
-> (SetChatMemberStatus -> String)
-> ([SetChatMemberStatus] -> ShowS)
-> Show SetChatMemberStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetChatMemberStatus] -> ShowS
$cshowList :: [SetChatMemberStatus] -> ShowS
show :: SetChatMemberStatus -> String
$cshow :: SetChatMemberStatus -> String
showsPrec :: Int -> SetChatMemberStatus -> ShowS
$cshowsPrec :: Int -> SetChatMemberStatus -> ShowS
Show, SetChatMemberStatus -> SetChatMemberStatus -> Bool
(SetChatMemberStatus -> SetChatMemberStatus -> Bool)
-> (SetChatMemberStatus -> SetChatMemberStatus -> Bool)
-> Eq SetChatMemberStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetChatMemberStatus -> SetChatMemberStatus -> Bool
$c/= :: SetChatMemberStatus -> SetChatMemberStatus -> Bool
== :: SetChatMemberStatus -> SetChatMemberStatus -> Bool
$c== :: SetChatMemberStatus -> SetChatMemberStatus -> Bool
Eq, (forall x. SetChatMemberStatus -> Rep SetChatMemberStatus x)
-> (forall x. Rep SetChatMemberStatus x -> SetChatMemberStatus)
-> Generic SetChatMemberStatus
forall x. Rep SetChatMemberStatus x -> SetChatMemberStatus
forall x. SetChatMemberStatus -> Rep SetChatMemberStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetChatMemberStatus x -> SetChatMemberStatus
$cfrom :: forall x. SetChatMemberStatus -> Rep SetChatMemberStatus x
Generic)

-- | Parameter of Function canTransferOwnership
data CanTransferOwnership
  = -- | Checks whether the current session can be used to transfer a chat ownership to another user
    CanTransferOwnership
      {
      }
  deriving (Int -> CanTransferOwnership -> ShowS
[CanTransferOwnership] -> ShowS
CanTransferOwnership -> String
(Int -> CanTransferOwnership -> ShowS)
-> (CanTransferOwnership -> String)
-> ([CanTransferOwnership] -> ShowS)
-> Show CanTransferOwnership
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CanTransferOwnership] -> ShowS
$cshowList :: [CanTransferOwnership] -> ShowS
show :: CanTransferOwnership -> String
$cshow :: CanTransferOwnership -> String
showsPrec :: Int -> CanTransferOwnership -> ShowS
$cshowsPrec :: Int -> CanTransferOwnership -> ShowS
Show, CanTransferOwnership -> CanTransferOwnership -> Bool
(CanTransferOwnership -> CanTransferOwnership -> Bool)
-> (CanTransferOwnership -> CanTransferOwnership -> Bool)
-> Eq CanTransferOwnership
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CanTransferOwnership -> CanTransferOwnership -> Bool
$c/= :: CanTransferOwnership -> CanTransferOwnership -> Bool
== :: CanTransferOwnership -> CanTransferOwnership -> Bool
$c== :: CanTransferOwnership -> CanTransferOwnership -> Bool
Eq, (forall x. CanTransferOwnership -> Rep CanTransferOwnership x)
-> (forall x. Rep CanTransferOwnership x -> CanTransferOwnership)
-> Generic CanTransferOwnership
forall x. Rep CanTransferOwnership x -> CanTransferOwnership
forall x. CanTransferOwnership -> Rep CanTransferOwnership x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CanTransferOwnership x -> CanTransferOwnership
$cfrom :: forall x. CanTransferOwnership -> Rep CanTransferOwnership x
Generic)

-- | Parameter of Function transferChatOwnership
data TransferChatOwnership
  = -- | Changes the owner of a chat. The current user must be a current owner of the chat. Use the method canTransferOwnership to check whether the ownership can be transferred from the current session. Available only for supergroups and channel chats
    TransferChatOwnership
      { -- | Chat identifier
        TransferChatOwnership -> Int
chat_id :: I53,
        -- | Identifier of the user to which transfer the ownership. The ownership can't be transferred to a bot or to a deleted user
        TransferChatOwnership -> Int
user_id :: I32,
        -- | The password of the current user
        TransferChatOwnership -> T
password :: T
      }
  deriving (Int -> TransferChatOwnership -> ShowS
[TransferChatOwnership] -> ShowS
TransferChatOwnership -> String
(Int -> TransferChatOwnership -> ShowS)
-> (TransferChatOwnership -> String)
-> ([TransferChatOwnership] -> ShowS)
-> Show TransferChatOwnership
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransferChatOwnership] -> ShowS
$cshowList :: [TransferChatOwnership] -> ShowS
show :: TransferChatOwnership -> String
$cshow :: TransferChatOwnership -> String
showsPrec :: Int -> TransferChatOwnership -> ShowS
$cshowsPrec :: Int -> TransferChatOwnership -> ShowS
Show, TransferChatOwnership -> TransferChatOwnership -> Bool
(TransferChatOwnership -> TransferChatOwnership -> Bool)
-> (TransferChatOwnership -> TransferChatOwnership -> Bool)
-> Eq TransferChatOwnership
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransferChatOwnership -> TransferChatOwnership -> Bool
$c/= :: TransferChatOwnership -> TransferChatOwnership -> Bool
== :: TransferChatOwnership -> TransferChatOwnership -> Bool
$c== :: TransferChatOwnership -> TransferChatOwnership -> Bool
Eq, (forall x. TransferChatOwnership -> Rep TransferChatOwnership x)
-> (forall x. Rep TransferChatOwnership x -> TransferChatOwnership)
-> Generic TransferChatOwnership
forall x. Rep TransferChatOwnership x -> TransferChatOwnership
forall x. TransferChatOwnership -> Rep TransferChatOwnership x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransferChatOwnership x -> TransferChatOwnership
$cfrom :: forall x. TransferChatOwnership -> Rep TransferChatOwnership x
Generic)

-- | Parameter of Function getChatMember
data GetChatMember
  = -- | Returns information about a single member of a chat
    GetChatMember
      { -- | Chat identifier
        GetChatMember -> Int
chat_id :: I53,
        -- | User identifier
        GetChatMember -> Int
user_id :: I32
      }
  deriving (Int -> GetChatMember -> ShowS
[GetChatMember] -> ShowS
GetChatMember -> String
(Int -> GetChatMember -> ShowS)
-> (GetChatMember -> String)
-> ([GetChatMember] -> ShowS)
-> Show GetChatMember
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatMember] -> ShowS
$cshowList :: [GetChatMember] -> ShowS
show :: GetChatMember -> String
$cshow :: GetChatMember -> String
showsPrec :: Int -> GetChatMember -> ShowS
$cshowsPrec :: Int -> GetChatMember -> ShowS
Show, GetChatMember -> GetChatMember -> Bool
(GetChatMember -> GetChatMember -> Bool)
-> (GetChatMember -> GetChatMember -> Bool) -> Eq GetChatMember
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatMember -> GetChatMember -> Bool
$c/= :: GetChatMember -> GetChatMember -> Bool
== :: GetChatMember -> GetChatMember -> Bool
$c== :: GetChatMember -> GetChatMember -> Bool
Eq, (forall x. GetChatMember -> Rep GetChatMember x)
-> (forall x. Rep GetChatMember x -> GetChatMember)
-> Generic GetChatMember
forall x. Rep GetChatMember x -> GetChatMember
forall x. GetChatMember -> Rep GetChatMember x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatMember x -> GetChatMember
$cfrom :: forall x. GetChatMember -> Rep GetChatMember x
Generic)

-- | Parameter of Function searchChatMembers
data SearchChatMembers
  = -- | Searches for a specified query in the first name, last name and username of the members of a specified chat. Requires administrator rights in channels
    SearchChatMembers
      { -- | Chat identifier
        SearchChatMembers -> Int
chat_id :: I53,
        -- | Query to search for
        SearchChatMembers -> T
query :: T,
        -- | The maximum number of users to be returned
        SearchChatMembers -> Int
limit :: I32,
        -- | The type of users to return. By default, chatMembersFilterMembers
        SearchChatMembers -> ChatMembersFilter
filter :: ChatMembersFilter
      }
  deriving (Int -> SearchChatMembers -> ShowS
[SearchChatMembers] -> ShowS
SearchChatMembers -> String
(Int -> SearchChatMembers -> ShowS)
-> (SearchChatMembers -> String)
-> ([SearchChatMembers] -> ShowS)
-> Show SearchChatMembers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchChatMembers] -> ShowS
$cshowList :: [SearchChatMembers] -> ShowS
show :: SearchChatMembers -> String
$cshow :: SearchChatMembers -> String
showsPrec :: Int -> SearchChatMembers -> ShowS
$cshowsPrec :: Int -> SearchChatMembers -> ShowS
Show, SearchChatMembers -> SearchChatMembers -> Bool
(SearchChatMembers -> SearchChatMembers -> Bool)
-> (SearchChatMembers -> SearchChatMembers -> Bool)
-> Eq SearchChatMembers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchChatMembers -> SearchChatMembers -> Bool
$c/= :: SearchChatMembers -> SearchChatMembers -> Bool
== :: SearchChatMembers -> SearchChatMembers -> Bool
$c== :: SearchChatMembers -> SearchChatMembers -> Bool
Eq, (forall x. SearchChatMembers -> Rep SearchChatMembers x)
-> (forall x. Rep SearchChatMembers x -> SearchChatMembers)
-> Generic SearchChatMembers
forall x. Rep SearchChatMembers x -> SearchChatMembers
forall x. SearchChatMembers -> Rep SearchChatMembers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchChatMembers x -> SearchChatMembers
$cfrom :: forall x. SearchChatMembers -> Rep SearchChatMembers x
Generic)

-- | Parameter of Function getChatAdministrators
data GetChatAdministrators
  = -- | Returns a list of administrators of the chat with their custom titles
    GetChatAdministrators
      { -- | Chat identifier
        GetChatAdministrators -> Int
chat_id :: I53
      }
  deriving (Int -> GetChatAdministrators -> ShowS
[GetChatAdministrators] -> ShowS
GetChatAdministrators -> String
(Int -> GetChatAdministrators -> ShowS)
-> (GetChatAdministrators -> String)
-> ([GetChatAdministrators] -> ShowS)
-> Show GetChatAdministrators
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatAdministrators] -> ShowS
$cshowList :: [GetChatAdministrators] -> ShowS
show :: GetChatAdministrators -> String
$cshow :: GetChatAdministrators -> String
showsPrec :: Int -> GetChatAdministrators -> ShowS
$cshowsPrec :: Int -> GetChatAdministrators -> ShowS
Show, GetChatAdministrators -> GetChatAdministrators -> Bool
(GetChatAdministrators -> GetChatAdministrators -> Bool)
-> (GetChatAdministrators -> GetChatAdministrators -> Bool)
-> Eq GetChatAdministrators
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatAdministrators -> GetChatAdministrators -> Bool
$c/= :: GetChatAdministrators -> GetChatAdministrators -> Bool
== :: GetChatAdministrators -> GetChatAdministrators -> Bool
$c== :: GetChatAdministrators -> GetChatAdministrators -> Bool
Eq, (forall x. GetChatAdministrators -> Rep GetChatAdministrators x)
-> (forall x. Rep GetChatAdministrators x -> GetChatAdministrators)
-> Generic GetChatAdministrators
forall x. Rep GetChatAdministrators x -> GetChatAdministrators
forall x. GetChatAdministrators -> Rep GetChatAdministrators x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatAdministrators x -> GetChatAdministrators
$cfrom :: forall x. GetChatAdministrators -> Rep GetChatAdministrators x
Generic)

-- | Parameter of Function clearAllDraftMessages
data ClearAllDraftMessages
  = -- | Clears draft messages in all chats
    ClearAllDraftMessages
      { -- | If true, local draft messages in secret chats will not be cleared
        ClearAllDraftMessages -> Bool
exclude_secret_chats :: Bool
      }
  deriving (Int -> ClearAllDraftMessages -> ShowS
[ClearAllDraftMessages] -> ShowS
ClearAllDraftMessages -> String
(Int -> ClearAllDraftMessages -> ShowS)
-> (ClearAllDraftMessages -> String)
-> ([ClearAllDraftMessages] -> ShowS)
-> Show ClearAllDraftMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearAllDraftMessages] -> ShowS
$cshowList :: [ClearAllDraftMessages] -> ShowS
show :: ClearAllDraftMessages -> String
$cshow :: ClearAllDraftMessages -> String
showsPrec :: Int -> ClearAllDraftMessages -> ShowS
$cshowsPrec :: Int -> ClearAllDraftMessages -> ShowS
Show, ClearAllDraftMessages -> ClearAllDraftMessages -> Bool
(ClearAllDraftMessages -> ClearAllDraftMessages -> Bool)
-> (ClearAllDraftMessages -> ClearAllDraftMessages -> Bool)
-> Eq ClearAllDraftMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearAllDraftMessages -> ClearAllDraftMessages -> Bool
$c/= :: ClearAllDraftMessages -> ClearAllDraftMessages -> Bool
== :: ClearAllDraftMessages -> ClearAllDraftMessages -> Bool
$c== :: ClearAllDraftMessages -> ClearAllDraftMessages -> Bool
Eq, (forall x. ClearAllDraftMessages -> Rep ClearAllDraftMessages x)
-> (forall x. Rep ClearAllDraftMessages x -> ClearAllDraftMessages)
-> Generic ClearAllDraftMessages
forall x. Rep ClearAllDraftMessages x -> ClearAllDraftMessages
forall x. ClearAllDraftMessages -> Rep ClearAllDraftMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClearAllDraftMessages x -> ClearAllDraftMessages
$cfrom :: forall x. ClearAllDraftMessages -> Rep ClearAllDraftMessages x
Generic)

-- | Parameter of Function getChatNotificationSettingsExceptions
data GetChatNotificationSettingsExceptions
  = -- | Returns list of chats with non-default notification settings
    GetChatNotificationSettingsExceptions
      { -- | If specified, only chats from the specified scope will be returned
        GetChatNotificationSettingsExceptions -> NotificationSettingsScope
scope :: NotificationSettingsScope,
        -- | If true, also chats with non-default sound will be returned
        GetChatNotificationSettingsExceptions -> Bool
compare_sound :: Bool
      }
  deriving (Int -> GetChatNotificationSettingsExceptions -> ShowS
[GetChatNotificationSettingsExceptions] -> ShowS
GetChatNotificationSettingsExceptions -> String
(Int -> GetChatNotificationSettingsExceptions -> ShowS)
-> (GetChatNotificationSettingsExceptions -> String)
-> ([GetChatNotificationSettingsExceptions] -> ShowS)
-> Show GetChatNotificationSettingsExceptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatNotificationSettingsExceptions] -> ShowS
$cshowList :: [GetChatNotificationSettingsExceptions] -> ShowS
show :: GetChatNotificationSettingsExceptions -> String
$cshow :: GetChatNotificationSettingsExceptions -> String
showsPrec :: Int -> GetChatNotificationSettingsExceptions -> ShowS
$cshowsPrec :: Int -> GetChatNotificationSettingsExceptions -> ShowS
Show, GetChatNotificationSettingsExceptions
-> GetChatNotificationSettingsExceptions -> Bool
(GetChatNotificationSettingsExceptions
 -> GetChatNotificationSettingsExceptions -> Bool)
-> (GetChatNotificationSettingsExceptions
    -> GetChatNotificationSettingsExceptions -> Bool)
-> Eq GetChatNotificationSettingsExceptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatNotificationSettingsExceptions
-> GetChatNotificationSettingsExceptions -> Bool
$c/= :: GetChatNotificationSettingsExceptions
-> GetChatNotificationSettingsExceptions -> Bool
== :: GetChatNotificationSettingsExceptions
-> GetChatNotificationSettingsExceptions -> Bool
$c== :: GetChatNotificationSettingsExceptions
-> GetChatNotificationSettingsExceptions -> Bool
Eq, (forall x.
 GetChatNotificationSettingsExceptions
 -> Rep GetChatNotificationSettingsExceptions x)
-> (forall x.
    Rep GetChatNotificationSettingsExceptions x
    -> GetChatNotificationSettingsExceptions)
-> Generic GetChatNotificationSettingsExceptions
forall x.
Rep GetChatNotificationSettingsExceptions x
-> GetChatNotificationSettingsExceptions
forall x.
GetChatNotificationSettingsExceptions
-> Rep GetChatNotificationSettingsExceptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetChatNotificationSettingsExceptions x
-> GetChatNotificationSettingsExceptions
$cfrom :: forall x.
GetChatNotificationSettingsExceptions
-> Rep GetChatNotificationSettingsExceptions x
Generic)

-- | Parameter of Function getScopeNotificationSettings
data GetScopeNotificationSettings
  = -- | Returns the notification settings for chats of a given type
    GetScopeNotificationSettings
      { -- | Types of chats for which to return the notification settings information
        GetScopeNotificationSettings -> NotificationSettingsScope
scope :: NotificationSettingsScope
      }
  deriving (Int -> GetScopeNotificationSettings -> ShowS
[GetScopeNotificationSettings] -> ShowS
GetScopeNotificationSettings -> String
(Int -> GetScopeNotificationSettings -> ShowS)
-> (GetScopeNotificationSettings -> String)
-> ([GetScopeNotificationSettings] -> ShowS)
-> Show GetScopeNotificationSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetScopeNotificationSettings] -> ShowS
$cshowList :: [GetScopeNotificationSettings] -> ShowS
show :: GetScopeNotificationSettings -> String
$cshow :: GetScopeNotificationSettings -> String
showsPrec :: Int -> GetScopeNotificationSettings -> ShowS
$cshowsPrec :: Int -> GetScopeNotificationSettings -> ShowS
Show, GetScopeNotificationSettings
-> GetScopeNotificationSettings -> Bool
(GetScopeNotificationSettings
 -> GetScopeNotificationSettings -> Bool)
-> (GetScopeNotificationSettings
    -> GetScopeNotificationSettings -> Bool)
-> Eq GetScopeNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetScopeNotificationSettings
-> GetScopeNotificationSettings -> Bool
$c/= :: GetScopeNotificationSettings
-> GetScopeNotificationSettings -> Bool
== :: GetScopeNotificationSettings
-> GetScopeNotificationSettings -> Bool
$c== :: GetScopeNotificationSettings
-> GetScopeNotificationSettings -> Bool
Eq, (forall x.
 GetScopeNotificationSettings -> Rep GetScopeNotificationSettings x)
-> (forall x.
    Rep GetScopeNotificationSettings x -> GetScopeNotificationSettings)
-> Generic GetScopeNotificationSettings
forall x.
Rep GetScopeNotificationSettings x -> GetScopeNotificationSettings
forall x.
GetScopeNotificationSettings -> Rep GetScopeNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetScopeNotificationSettings x -> GetScopeNotificationSettings
$cfrom :: forall x.
GetScopeNotificationSettings -> Rep GetScopeNotificationSettings x
Generic)

-- | Parameter of Function setScopeNotificationSettings
data SetScopeNotificationSettings
  = -- | Changes notification settings for chats of a given type
    SetScopeNotificationSettings
      { -- | Types of chats for which to change the notification settings
        SetScopeNotificationSettings -> NotificationSettingsScope
scope :: NotificationSettingsScope,
        -- | The new notification settings for the given scope
        SetScopeNotificationSettings -> ScopeNotificationSettings
notification_settings :: ScopeNotificationSettings
      }
  deriving (Int -> SetScopeNotificationSettings -> ShowS
[SetScopeNotificationSettings] -> ShowS
SetScopeNotificationSettings -> String
(Int -> SetScopeNotificationSettings -> ShowS)
-> (SetScopeNotificationSettings -> String)
-> ([SetScopeNotificationSettings] -> ShowS)
-> Show SetScopeNotificationSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetScopeNotificationSettings] -> ShowS
$cshowList :: [SetScopeNotificationSettings] -> ShowS
show :: SetScopeNotificationSettings -> String
$cshow :: SetScopeNotificationSettings -> String
showsPrec :: Int -> SetScopeNotificationSettings -> ShowS
$cshowsPrec :: Int -> SetScopeNotificationSettings -> ShowS
Show, SetScopeNotificationSettings
-> SetScopeNotificationSettings -> Bool
(SetScopeNotificationSettings
 -> SetScopeNotificationSettings -> Bool)
-> (SetScopeNotificationSettings
    -> SetScopeNotificationSettings -> Bool)
-> Eq SetScopeNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetScopeNotificationSettings
-> SetScopeNotificationSettings -> Bool
$c/= :: SetScopeNotificationSettings
-> SetScopeNotificationSettings -> Bool
== :: SetScopeNotificationSettings
-> SetScopeNotificationSettings -> Bool
$c== :: SetScopeNotificationSettings
-> SetScopeNotificationSettings -> Bool
Eq, (forall x.
 SetScopeNotificationSettings -> Rep SetScopeNotificationSettings x)
-> (forall x.
    Rep SetScopeNotificationSettings x -> SetScopeNotificationSettings)
-> Generic SetScopeNotificationSettings
forall x.
Rep SetScopeNotificationSettings x -> SetScopeNotificationSettings
forall x.
SetScopeNotificationSettings -> Rep SetScopeNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetScopeNotificationSettings x -> SetScopeNotificationSettings
$cfrom :: forall x.
SetScopeNotificationSettings -> Rep SetScopeNotificationSettings x
Generic)

-- | Parameter of Function resetAllNotificationSettings
data ResetAllNotificationSettings
  = -- | Resets all notification settings to their default values. By default, all chats are unmuted, the sound is set to "default" and message previews are shown
    ResetAllNotificationSettings
      {
      }
  deriving (Int -> ResetAllNotificationSettings -> ShowS
[ResetAllNotificationSettings] -> ShowS
ResetAllNotificationSettings -> String
(Int -> ResetAllNotificationSettings -> ShowS)
-> (ResetAllNotificationSettings -> String)
-> ([ResetAllNotificationSettings] -> ShowS)
-> Show ResetAllNotificationSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetAllNotificationSettings] -> ShowS
$cshowList :: [ResetAllNotificationSettings] -> ShowS
show :: ResetAllNotificationSettings -> String
$cshow :: ResetAllNotificationSettings -> String
showsPrec :: Int -> ResetAllNotificationSettings -> ShowS
$cshowsPrec :: Int -> ResetAllNotificationSettings -> ShowS
Show, ResetAllNotificationSettings
-> ResetAllNotificationSettings -> Bool
(ResetAllNotificationSettings
 -> ResetAllNotificationSettings -> Bool)
-> (ResetAllNotificationSettings
    -> ResetAllNotificationSettings -> Bool)
-> Eq ResetAllNotificationSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetAllNotificationSettings
-> ResetAllNotificationSettings -> Bool
$c/= :: ResetAllNotificationSettings
-> ResetAllNotificationSettings -> Bool
== :: ResetAllNotificationSettings
-> ResetAllNotificationSettings -> Bool
$c== :: ResetAllNotificationSettings
-> ResetAllNotificationSettings -> Bool
Eq, (forall x.
 ResetAllNotificationSettings -> Rep ResetAllNotificationSettings x)
-> (forall x.
    Rep ResetAllNotificationSettings x -> ResetAllNotificationSettings)
-> Generic ResetAllNotificationSettings
forall x.
Rep ResetAllNotificationSettings x -> ResetAllNotificationSettings
forall x.
ResetAllNotificationSettings -> Rep ResetAllNotificationSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResetAllNotificationSettings x -> ResetAllNotificationSettings
$cfrom :: forall x.
ResetAllNotificationSettings -> Rep ResetAllNotificationSettings x
Generic)

-- | Parameter of Function setPinnedChats
data SetPinnedChats
  = -- | Changes the order of pinned chats
    SetPinnedChats
      { -- | Chat list in which to change the order of pinned chats
        SetPinnedChats -> ChatList
chat_list :: ChatList,
        -- | The new list of pinned chats
        SetPinnedChats -> [Int]
chat_ids :: ([]) (I53)
      }
  deriving (Int -> SetPinnedChats -> ShowS
[SetPinnedChats] -> ShowS
SetPinnedChats -> String
(Int -> SetPinnedChats -> ShowS)
-> (SetPinnedChats -> String)
-> ([SetPinnedChats] -> ShowS)
-> Show SetPinnedChats
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPinnedChats] -> ShowS
$cshowList :: [SetPinnedChats] -> ShowS
show :: SetPinnedChats -> String
$cshow :: SetPinnedChats -> String
showsPrec :: Int -> SetPinnedChats -> ShowS
$cshowsPrec :: Int -> SetPinnedChats -> ShowS
Show, SetPinnedChats -> SetPinnedChats -> Bool
(SetPinnedChats -> SetPinnedChats -> Bool)
-> (SetPinnedChats -> SetPinnedChats -> Bool) -> Eq SetPinnedChats
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPinnedChats -> SetPinnedChats -> Bool
$c/= :: SetPinnedChats -> SetPinnedChats -> Bool
== :: SetPinnedChats -> SetPinnedChats -> Bool
$c== :: SetPinnedChats -> SetPinnedChats -> Bool
Eq, (forall x. SetPinnedChats -> Rep SetPinnedChats x)
-> (forall x. Rep SetPinnedChats x -> SetPinnedChats)
-> Generic SetPinnedChats
forall x. Rep SetPinnedChats x -> SetPinnedChats
forall x. SetPinnedChats -> Rep SetPinnedChats x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetPinnedChats x -> SetPinnedChats
$cfrom :: forall x. SetPinnedChats -> Rep SetPinnedChats x
Generic)

-- | Parameter of Function downloadFile
data DownloadFile
  = -- | Downloads a file from the cloud. Download progress and completion of the download will be notified through updateFile updates
    DownloadFile
      { -- | Identifier of the file to download
        DownloadFile -> Int
file_id :: I32,
        -- | Priority of the download (1-32). The higher the priority, the earlier the file will be downloaded. If the priorities of two files are equal, then the last one for which downloadFile was called will be downloaded first
        DownloadFile -> Int
priority :: I32,
        -- | The starting position from which the file should be downloaded
        DownloadFile -> Int
offset :: I32,
        -- | Number of bytes which should be downloaded starting from the "offset" position before the download will be automatically cancelled; use 0 to download without a limit
        DownloadFile -> Int
limit :: I32,
        -- | If false, this request returns file state just after the download has been started. If true, this request returns file state only after
        DownloadFile -> Bool
synchronous :: Bool
      }
  deriving (Int -> DownloadFile -> ShowS
[DownloadFile] -> ShowS
DownloadFile -> String
(Int -> DownloadFile -> ShowS)
-> (DownloadFile -> String)
-> ([DownloadFile] -> ShowS)
-> Show DownloadFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DownloadFile] -> ShowS
$cshowList :: [DownloadFile] -> ShowS
show :: DownloadFile -> String
$cshow :: DownloadFile -> String
showsPrec :: Int -> DownloadFile -> ShowS
$cshowsPrec :: Int -> DownloadFile -> ShowS
Show, DownloadFile -> DownloadFile -> Bool
(DownloadFile -> DownloadFile -> Bool)
-> (DownloadFile -> DownloadFile -> Bool) -> Eq DownloadFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DownloadFile -> DownloadFile -> Bool
$c/= :: DownloadFile -> DownloadFile -> Bool
== :: DownloadFile -> DownloadFile -> Bool
$c== :: DownloadFile -> DownloadFile -> Bool
Eq, (forall x. DownloadFile -> Rep DownloadFile x)
-> (forall x. Rep DownloadFile x -> DownloadFile)
-> Generic DownloadFile
forall x. Rep DownloadFile x -> DownloadFile
forall x. DownloadFile -> Rep DownloadFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DownloadFile x -> DownloadFile
$cfrom :: forall x. DownloadFile -> Rep DownloadFile x
Generic)

-- | Parameter of Function getFileDownloadedPrefixSize
data GetFileDownloadedPrefixSize
  = -- | Returns file downloaded prefix size from a given offset
    GetFileDownloadedPrefixSize
      { -- | Identifier of the file
        GetFileDownloadedPrefixSize -> Int
file_id :: I32,
        -- | Offset from which downloaded prefix size should be calculated
        GetFileDownloadedPrefixSize -> Int
offset :: I32
      }
  deriving (Int -> GetFileDownloadedPrefixSize -> ShowS
[GetFileDownloadedPrefixSize] -> ShowS
GetFileDownloadedPrefixSize -> String
(Int -> GetFileDownloadedPrefixSize -> ShowS)
-> (GetFileDownloadedPrefixSize -> String)
-> ([GetFileDownloadedPrefixSize] -> ShowS)
-> Show GetFileDownloadedPrefixSize
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFileDownloadedPrefixSize] -> ShowS
$cshowList :: [GetFileDownloadedPrefixSize] -> ShowS
show :: GetFileDownloadedPrefixSize -> String
$cshow :: GetFileDownloadedPrefixSize -> String
showsPrec :: Int -> GetFileDownloadedPrefixSize -> ShowS
$cshowsPrec :: Int -> GetFileDownloadedPrefixSize -> ShowS
Show, GetFileDownloadedPrefixSize -> GetFileDownloadedPrefixSize -> Bool
(GetFileDownloadedPrefixSize
 -> GetFileDownloadedPrefixSize -> Bool)
-> (GetFileDownloadedPrefixSize
    -> GetFileDownloadedPrefixSize -> Bool)
-> Eq GetFileDownloadedPrefixSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFileDownloadedPrefixSize -> GetFileDownloadedPrefixSize -> Bool
$c/= :: GetFileDownloadedPrefixSize -> GetFileDownloadedPrefixSize -> Bool
== :: GetFileDownloadedPrefixSize -> GetFileDownloadedPrefixSize -> Bool
$c== :: GetFileDownloadedPrefixSize -> GetFileDownloadedPrefixSize -> Bool
Eq, (forall x.
 GetFileDownloadedPrefixSize -> Rep GetFileDownloadedPrefixSize x)
-> (forall x.
    Rep GetFileDownloadedPrefixSize x -> GetFileDownloadedPrefixSize)
-> Generic GetFileDownloadedPrefixSize
forall x.
Rep GetFileDownloadedPrefixSize x -> GetFileDownloadedPrefixSize
forall x.
GetFileDownloadedPrefixSize -> Rep GetFileDownloadedPrefixSize x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetFileDownloadedPrefixSize x -> GetFileDownloadedPrefixSize
$cfrom :: forall x.
GetFileDownloadedPrefixSize -> Rep GetFileDownloadedPrefixSize x
Generic)

-- | Parameter of Function cancelDownloadFile
data CancelDownloadFile
  = -- | Stops the downloading of a file. If a file has already been downloaded, does nothing
    CancelDownloadFile
      { -- | Identifier of a file to stop downloading
        CancelDownloadFile -> Int
file_id :: I32,
        -- | Pass true to stop downloading only if it hasn't been started, i.e. request hasn't been sent to server
        CancelDownloadFile -> Bool
only_if_pending :: Bool
      }
  deriving (Int -> CancelDownloadFile -> ShowS
[CancelDownloadFile] -> ShowS
CancelDownloadFile -> String
(Int -> CancelDownloadFile -> ShowS)
-> (CancelDownloadFile -> String)
-> ([CancelDownloadFile] -> ShowS)
-> Show CancelDownloadFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelDownloadFile] -> ShowS
$cshowList :: [CancelDownloadFile] -> ShowS
show :: CancelDownloadFile -> String
$cshow :: CancelDownloadFile -> String
showsPrec :: Int -> CancelDownloadFile -> ShowS
$cshowsPrec :: Int -> CancelDownloadFile -> ShowS
Show, CancelDownloadFile -> CancelDownloadFile -> Bool
(CancelDownloadFile -> CancelDownloadFile -> Bool)
-> (CancelDownloadFile -> CancelDownloadFile -> Bool)
-> Eq CancelDownloadFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelDownloadFile -> CancelDownloadFile -> Bool
$c/= :: CancelDownloadFile -> CancelDownloadFile -> Bool
== :: CancelDownloadFile -> CancelDownloadFile -> Bool
$c== :: CancelDownloadFile -> CancelDownloadFile -> Bool
Eq, (forall x. CancelDownloadFile -> Rep CancelDownloadFile x)
-> (forall x. Rep CancelDownloadFile x -> CancelDownloadFile)
-> Generic CancelDownloadFile
forall x. Rep CancelDownloadFile x -> CancelDownloadFile
forall x. CancelDownloadFile -> Rep CancelDownloadFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelDownloadFile x -> CancelDownloadFile
$cfrom :: forall x. CancelDownloadFile -> Rep CancelDownloadFile x
Generic)

-- | Parameter of Function uploadFile
data UploadFile
  = -- | Asynchronously uploads a file to the cloud without sending it in a message. updateFile will be used to notify about upload progress and successful completion of the upload. The file will not have a persistent remote identifier until it will be sent in a message
    UploadFile
      { -- | File to upload
        UploadFile -> InputFile
file :: InputFile,
        -- | File type
        UploadFile -> FileType
file_type :: FileType,
        -- | Priority of the upload (1-32). The higher the priority, the earlier the file will be uploaded. If the priorities of two files are equal, then the first one for which uploadFile was called will be uploaded first
        UploadFile -> Int
priority :: I32
      }
  deriving (Int -> UploadFile -> ShowS
[UploadFile] -> ShowS
UploadFile -> String
(Int -> UploadFile -> ShowS)
-> (UploadFile -> String)
-> ([UploadFile] -> ShowS)
-> Show UploadFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadFile] -> ShowS
$cshowList :: [UploadFile] -> ShowS
show :: UploadFile -> String
$cshow :: UploadFile -> String
showsPrec :: Int -> UploadFile -> ShowS
$cshowsPrec :: Int -> UploadFile -> ShowS
Show, UploadFile -> UploadFile -> Bool
(UploadFile -> UploadFile -> Bool)
-> (UploadFile -> UploadFile -> Bool) -> Eq UploadFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadFile -> UploadFile -> Bool
$c/= :: UploadFile -> UploadFile -> Bool
== :: UploadFile -> UploadFile -> Bool
$c== :: UploadFile -> UploadFile -> Bool
Eq, (forall x. UploadFile -> Rep UploadFile x)
-> (forall x. Rep UploadFile x -> UploadFile) -> Generic UploadFile
forall x. Rep UploadFile x -> UploadFile
forall x. UploadFile -> Rep UploadFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadFile x -> UploadFile
$cfrom :: forall x. UploadFile -> Rep UploadFile x
Generic)

-- | Parameter of Function cancelUploadFile
data CancelUploadFile
  = -- | Stops the uploading of a file. Supported only for files uploaded by using uploadFile. For other files the behavior is undefined
    CancelUploadFile
      { -- | Identifier of the file to stop uploading
        CancelUploadFile -> Int
file_id :: I32
      }
  deriving (Int -> CancelUploadFile -> ShowS
[CancelUploadFile] -> ShowS
CancelUploadFile -> String
(Int -> CancelUploadFile -> ShowS)
-> (CancelUploadFile -> String)
-> ([CancelUploadFile] -> ShowS)
-> Show CancelUploadFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelUploadFile] -> ShowS
$cshowList :: [CancelUploadFile] -> ShowS
show :: CancelUploadFile -> String
$cshow :: CancelUploadFile -> String
showsPrec :: Int -> CancelUploadFile -> ShowS
$cshowsPrec :: Int -> CancelUploadFile -> ShowS
Show, CancelUploadFile -> CancelUploadFile -> Bool
(CancelUploadFile -> CancelUploadFile -> Bool)
-> (CancelUploadFile -> CancelUploadFile -> Bool)
-> Eq CancelUploadFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelUploadFile -> CancelUploadFile -> Bool
$c/= :: CancelUploadFile -> CancelUploadFile -> Bool
== :: CancelUploadFile -> CancelUploadFile -> Bool
$c== :: CancelUploadFile -> CancelUploadFile -> Bool
Eq, (forall x. CancelUploadFile -> Rep CancelUploadFile x)
-> (forall x. Rep CancelUploadFile x -> CancelUploadFile)
-> Generic CancelUploadFile
forall x. Rep CancelUploadFile x -> CancelUploadFile
forall x. CancelUploadFile -> Rep CancelUploadFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelUploadFile x -> CancelUploadFile
$cfrom :: forall x. CancelUploadFile -> Rep CancelUploadFile x
Generic)

-- | Parameter of Function writeGeneratedFilePart
data WriteGeneratedFilePart
  = -- | Writes a part of a generated file. This method is intended to be used only if the client has no direct access to TDLib's file system, because it is usually slower than a direct write to the destination file
    WriteGeneratedFilePart
      { -- | The identifier of the generation process
        WriteGeneratedFilePart -> I64
generation_id :: I64,
        -- | The offset from which to write the data to the file
        WriteGeneratedFilePart -> Int
offset :: I32,
        -- | The data to write
        WriteGeneratedFilePart -> ByteString64
data_ :: ByteString64
      }
  deriving (Int -> WriteGeneratedFilePart -> ShowS
[WriteGeneratedFilePart] -> ShowS
WriteGeneratedFilePart -> String
(Int -> WriteGeneratedFilePart -> ShowS)
-> (WriteGeneratedFilePart -> String)
-> ([WriteGeneratedFilePart] -> ShowS)
-> Show WriteGeneratedFilePart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WriteGeneratedFilePart] -> ShowS
$cshowList :: [WriteGeneratedFilePart] -> ShowS
show :: WriteGeneratedFilePart -> String
$cshow :: WriteGeneratedFilePart -> String
showsPrec :: Int -> WriteGeneratedFilePart -> ShowS
$cshowsPrec :: Int -> WriteGeneratedFilePart -> ShowS
Show, WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool
(WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool)
-> (WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool)
-> Eq WriteGeneratedFilePart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool
$c/= :: WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool
== :: WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool
$c== :: WriteGeneratedFilePart -> WriteGeneratedFilePart -> Bool
Eq, (forall x. WriteGeneratedFilePart -> Rep WriteGeneratedFilePart x)
-> (forall x.
    Rep WriteGeneratedFilePart x -> WriteGeneratedFilePart)
-> Generic WriteGeneratedFilePart
forall x. Rep WriteGeneratedFilePart x -> WriteGeneratedFilePart
forall x. WriteGeneratedFilePart -> Rep WriteGeneratedFilePart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep WriteGeneratedFilePart x -> WriteGeneratedFilePart
$cfrom :: forall x. WriteGeneratedFilePart -> Rep WriteGeneratedFilePart x
Generic)

-- | Parameter of Function setFileGenerationProgress
data SetFileGenerationProgress
  = -- | Informs TDLib on a file generation progress
    SetFileGenerationProgress
      { -- | The identifier of the generation process
        SetFileGenerationProgress -> I64
generation_id :: I64,
        -- | Expected size of the generated file, in bytes; 0 if unknown
        SetFileGenerationProgress -> Int
expected_size :: I32,
        -- | The number of bytes already generated
        SetFileGenerationProgress -> Int
local_prefix_size :: I32
      }
  deriving (Int -> SetFileGenerationProgress -> ShowS
[SetFileGenerationProgress] -> ShowS
SetFileGenerationProgress -> String
(Int -> SetFileGenerationProgress -> ShowS)
-> (SetFileGenerationProgress -> String)
-> ([SetFileGenerationProgress] -> ShowS)
-> Show SetFileGenerationProgress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetFileGenerationProgress] -> ShowS
$cshowList :: [SetFileGenerationProgress] -> ShowS
show :: SetFileGenerationProgress -> String
$cshow :: SetFileGenerationProgress -> String
showsPrec :: Int -> SetFileGenerationProgress -> ShowS
$cshowsPrec :: Int -> SetFileGenerationProgress -> ShowS
Show, SetFileGenerationProgress -> SetFileGenerationProgress -> Bool
(SetFileGenerationProgress -> SetFileGenerationProgress -> Bool)
-> (SetFileGenerationProgress -> SetFileGenerationProgress -> Bool)
-> Eq SetFileGenerationProgress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetFileGenerationProgress -> SetFileGenerationProgress -> Bool
$c/= :: SetFileGenerationProgress -> SetFileGenerationProgress -> Bool
== :: SetFileGenerationProgress -> SetFileGenerationProgress -> Bool
$c== :: SetFileGenerationProgress -> SetFileGenerationProgress -> Bool
Eq, (forall x.
 SetFileGenerationProgress -> Rep SetFileGenerationProgress x)
-> (forall x.
    Rep SetFileGenerationProgress x -> SetFileGenerationProgress)
-> Generic SetFileGenerationProgress
forall x.
Rep SetFileGenerationProgress x -> SetFileGenerationProgress
forall x.
SetFileGenerationProgress -> Rep SetFileGenerationProgress x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetFileGenerationProgress x -> SetFileGenerationProgress
$cfrom :: forall x.
SetFileGenerationProgress -> Rep SetFileGenerationProgress x
Generic)

-- | Parameter of Function finishFileGeneration
data FinishFileGeneration
  = -- | Finishes the file generation
    FinishFileGeneration
      { -- | The identifier of the generation process
        FinishFileGeneration -> I64
generation_id :: I64,
        -- | If set, means that file generation has failed and should be terminated
        FinishFileGeneration -> Error
error :: Error
      }
  deriving (Int -> FinishFileGeneration -> ShowS
[FinishFileGeneration] -> ShowS
FinishFileGeneration -> String
(Int -> FinishFileGeneration -> ShowS)
-> (FinishFileGeneration -> String)
-> ([FinishFileGeneration] -> ShowS)
-> Show FinishFileGeneration
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FinishFileGeneration] -> ShowS
$cshowList :: [FinishFileGeneration] -> ShowS
show :: FinishFileGeneration -> String
$cshow :: FinishFileGeneration -> String
showsPrec :: Int -> FinishFileGeneration -> ShowS
$cshowsPrec :: Int -> FinishFileGeneration -> ShowS
Show, FinishFileGeneration -> FinishFileGeneration -> Bool
(FinishFileGeneration -> FinishFileGeneration -> Bool)
-> (FinishFileGeneration -> FinishFileGeneration -> Bool)
-> Eq FinishFileGeneration
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FinishFileGeneration -> FinishFileGeneration -> Bool
$c/= :: FinishFileGeneration -> FinishFileGeneration -> Bool
== :: FinishFileGeneration -> FinishFileGeneration -> Bool
$c== :: FinishFileGeneration -> FinishFileGeneration -> Bool
Eq, (forall x. FinishFileGeneration -> Rep FinishFileGeneration x)
-> (forall x. Rep FinishFileGeneration x -> FinishFileGeneration)
-> Generic FinishFileGeneration
forall x. Rep FinishFileGeneration x -> FinishFileGeneration
forall x. FinishFileGeneration -> Rep FinishFileGeneration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FinishFileGeneration x -> FinishFileGeneration
$cfrom :: forall x. FinishFileGeneration -> Rep FinishFileGeneration x
Generic)

-- | Parameter of Function readFilePart
data ReadFilePart
  = -- | Reads a part of a file from the TDLib file cache and returns read bytes. This method is intended to be used only if the client has no direct access to TDLib's file system, because it is usually slower than a direct read from the file
    ReadFilePart
      { -- | Identifier of the file. The file must be located in the TDLib file cache
        ReadFilePart -> Int
file_id :: I32,
        -- | The offset from which to read the file
        ReadFilePart -> Int
offset :: I32,
        -- | Number of bytes to read. An error will be returned if there are not enough bytes available in the file from the specified position. Pass 0 to read all available data from the specified position
        ReadFilePart -> Int
count :: I32
      }
  deriving (Int -> ReadFilePart -> ShowS
[ReadFilePart] -> ShowS
ReadFilePart -> String
(Int -> ReadFilePart -> ShowS)
-> (ReadFilePart -> String)
-> ([ReadFilePart] -> ShowS)
-> Show ReadFilePart
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReadFilePart] -> ShowS
$cshowList :: [ReadFilePart] -> ShowS
show :: ReadFilePart -> String
$cshow :: ReadFilePart -> String
showsPrec :: Int -> ReadFilePart -> ShowS
$cshowsPrec :: Int -> ReadFilePart -> ShowS
Show, ReadFilePart -> ReadFilePart -> Bool
(ReadFilePart -> ReadFilePart -> Bool)
-> (ReadFilePart -> ReadFilePart -> Bool) -> Eq ReadFilePart
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReadFilePart -> ReadFilePart -> Bool
$c/= :: ReadFilePart -> ReadFilePart -> Bool
== :: ReadFilePart -> ReadFilePart -> Bool
$c== :: ReadFilePart -> ReadFilePart -> Bool
Eq, (forall x. ReadFilePart -> Rep ReadFilePart x)
-> (forall x. Rep ReadFilePart x -> ReadFilePart)
-> Generic ReadFilePart
forall x. Rep ReadFilePart x -> ReadFilePart
forall x. ReadFilePart -> Rep ReadFilePart x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReadFilePart x -> ReadFilePart
$cfrom :: forall x. ReadFilePart -> Rep ReadFilePart x
Generic)

-- | Parameter of Function deleteFile
data DeleteFile
  = -- | Deletes a file from the TDLib file cache
    DeleteFile
      { -- | Identifier of the file to delete
        DeleteFile -> Int
file_id :: I32
      }
  deriving (Int -> DeleteFile -> ShowS
[DeleteFile] -> ShowS
DeleteFile -> String
(Int -> DeleteFile -> ShowS)
-> (DeleteFile -> String)
-> ([DeleteFile] -> ShowS)
-> Show DeleteFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteFile] -> ShowS
$cshowList :: [DeleteFile] -> ShowS
show :: DeleteFile -> String
$cshow :: DeleteFile -> String
showsPrec :: Int -> DeleteFile -> ShowS
$cshowsPrec :: Int -> DeleteFile -> ShowS
Show, DeleteFile -> DeleteFile -> Bool
(DeleteFile -> DeleteFile -> Bool)
-> (DeleteFile -> DeleteFile -> Bool) -> Eq DeleteFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteFile -> DeleteFile -> Bool
$c/= :: DeleteFile -> DeleteFile -> Bool
== :: DeleteFile -> DeleteFile -> Bool
$c== :: DeleteFile -> DeleteFile -> Bool
Eq, (forall x. DeleteFile -> Rep DeleteFile x)
-> (forall x. Rep DeleteFile x -> DeleteFile) -> Generic DeleteFile
forall x. Rep DeleteFile x -> DeleteFile
forall x. DeleteFile -> Rep DeleteFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteFile x -> DeleteFile
$cfrom :: forall x. DeleteFile -> Rep DeleteFile x
Generic)

-- | Parameter of Function generateChatInviteLink
data GenerateChatInviteLink
  = -- | Generates a new invite link for a chat; the previously generated link is revoked. Available for basic groups, supergroups, and channels. Requires administrator privileges and can_invite_users right
    GenerateChatInviteLink
      { -- | Chat identifier
        GenerateChatInviteLink -> Int
chat_id :: I53
      }
  deriving (Int -> GenerateChatInviteLink -> ShowS
[GenerateChatInviteLink] -> ShowS
GenerateChatInviteLink -> String
(Int -> GenerateChatInviteLink -> ShowS)
-> (GenerateChatInviteLink -> String)
-> ([GenerateChatInviteLink] -> ShowS)
-> Show GenerateChatInviteLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenerateChatInviteLink] -> ShowS
$cshowList :: [GenerateChatInviteLink] -> ShowS
show :: GenerateChatInviteLink -> String
$cshow :: GenerateChatInviteLink -> String
showsPrec :: Int -> GenerateChatInviteLink -> ShowS
$cshowsPrec :: Int -> GenerateChatInviteLink -> ShowS
Show, GenerateChatInviteLink -> GenerateChatInviteLink -> Bool
(GenerateChatInviteLink -> GenerateChatInviteLink -> Bool)
-> (GenerateChatInviteLink -> GenerateChatInviteLink -> Bool)
-> Eq GenerateChatInviteLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenerateChatInviteLink -> GenerateChatInviteLink -> Bool
$c/= :: GenerateChatInviteLink -> GenerateChatInviteLink -> Bool
== :: GenerateChatInviteLink -> GenerateChatInviteLink -> Bool
$c== :: GenerateChatInviteLink -> GenerateChatInviteLink -> Bool
Eq, (forall x. GenerateChatInviteLink -> Rep GenerateChatInviteLink x)
-> (forall x.
    Rep GenerateChatInviteLink x -> GenerateChatInviteLink)
-> Generic GenerateChatInviteLink
forall x. Rep GenerateChatInviteLink x -> GenerateChatInviteLink
forall x. GenerateChatInviteLink -> Rep GenerateChatInviteLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GenerateChatInviteLink x -> GenerateChatInviteLink
$cfrom :: forall x. GenerateChatInviteLink -> Rep GenerateChatInviteLink x
Generic)

-- | Parameter of Function checkChatInviteLink
data CheckChatInviteLink
  = -- | Checks the validity of an invite link for a chat and returns information about the corresponding chat
    CheckChatInviteLink
      { -- | Invite link to be checked; should begin with "https://t.me/joinchat/", "https://telegram.me/joinchat/", or "https://telegram.dog/joinchat/"
        CheckChatInviteLink -> T
invite_link :: T
      }
  deriving (Int -> CheckChatInviteLink -> ShowS
[CheckChatInviteLink] -> ShowS
CheckChatInviteLink -> String
(Int -> CheckChatInviteLink -> ShowS)
-> (CheckChatInviteLink -> String)
-> ([CheckChatInviteLink] -> ShowS)
-> Show CheckChatInviteLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckChatInviteLink] -> ShowS
$cshowList :: [CheckChatInviteLink] -> ShowS
show :: CheckChatInviteLink -> String
$cshow :: CheckChatInviteLink -> String
showsPrec :: Int -> CheckChatInviteLink -> ShowS
$cshowsPrec :: Int -> CheckChatInviteLink -> ShowS
Show, CheckChatInviteLink -> CheckChatInviteLink -> Bool
(CheckChatInviteLink -> CheckChatInviteLink -> Bool)
-> (CheckChatInviteLink -> CheckChatInviteLink -> Bool)
-> Eq CheckChatInviteLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckChatInviteLink -> CheckChatInviteLink -> Bool
$c/= :: CheckChatInviteLink -> CheckChatInviteLink -> Bool
== :: CheckChatInviteLink -> CheckChatInviteLink -> Bool
$c== :: CheckChatInviteLink -> CheckChatInviteLink -> Bool
Eq, (forall x. CheckChatInviteLink -> Rep CheckChatInviteLink x)
-> (forall x. Rep CheckChatInviteLink x -> CheckChatInviteLink)
-> Generic CheckChatInviteLink
forall x. Rep CheckChatInviteLink x -> CheckChatInviteLink
forall x. CheckChatInviteLink -> Rep CheckChatInviteLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CheckChatInviteLink x -> CheckChatInviteLink
$cfrom :: forall x. CheckChatInviteLink -> Rep CheckChatInviteLink x
Generic)

-- | Parameter of Function joinChatByInviteLink
data JoinChatByInviteLink
  = -- | Uses an invite link to add the current user to the chat if possible. The new member will not be added until the chat state has been synchronized with the server
    JoinChatByInviteLink
      { -- | Invite link to import; should begin with "https://t.me/joinchat/", "https://telegram.me/joinchat/", or "https://telegram.dog/joinchat/"
        JoinChatByInviteLink -> T
invite_link :: T
      }
  deriving (Int -> JoinChatByInviteLink -> ShowS
[JoinChatByInviteLink] -> ShowS
JoinChatByInviteLink -> String
(Int -> JoinChatByInviteLink -> ShowS)
-> (JoinChatByInviteLink -> String)
-> ([JoinChatByInviteLink] -> ShowS)
-> Show JoinChatByInviteLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JoinChatByInviteLink] -> ShowS
$cshowList :: [JoinChatByInviteLink] -> ShowS
show :: JoinChatByInviteLink -> String
$cshow :: JoinChatByInviteLink -> String
showsPrec :: Int -> JoinChatByInviteLink -> ShowS
$cshowsPrec :: Int -> JoinChatByInviteLink -> ShowS
Show, JoinChatByInviteLink -> JoinChatByInviteLink -> Bool
(JoinChatByInviteLink -> JoinChatByInviteLink -> Bool)
-> (JoinChatByInviteLink -> JoinChatByInviteLink -> Bool)
-> Eq JoinChatByInviteLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JoinChatByInviteLink -> JoinChatByInviteLink -> Bool
$c/= :: JoinChatByInviteLink -> JoinChatByInviteLink -> Bool
== :: JoinChatByInviteLink -> JoinChatByInviteLink -> Bool
$c== :: JoinChatByInviteLink -> JoinChatByInviteLink -> Bool
Eq, (forall x. JoinChatByInviteLink -> Rep JoinChatByInviteLink x)
-> (forall x. Rep JoinChatByInviteLink x -> JoinChatByInviteLink)
-> Generic JoinChatByInviteLink
forall x. Rep JoinChatByInviteLink x -> JoinChatByInviteLink
forall x. JoinChatByInviteLink -> Rep JoinChatByInviteLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JoinChatByInviteLink x -> JoinChatByInviteLink
$cfrom :: forall x. JoinChatByInviteLink -> Rep JoinChatByInviteLink x
Generic)

-- | Parameter of Function createCall
data CreateCall
  = -- | Creates a new call
    CreateCall
      { -- | Identifier of the user to be called
        CreateCall -> Int
user_id :: I32,
        -- | Description of the call protocols supported by the client
        CreateCall -> CallProtocol
protocol :: CallProtocol
      }
  deriving (Int -> CreateCall -> ShowS
[CreateCall] -> ShowS
CreateCall -> String
(Int -> CreateCall -> ShowS)
-> (CreateCall -> String)
-> ([CreateCall] -> ShowS)
-> Show CreateCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCall] -> ShowS
$cshowList :: [CreateCall] -> ShowS
show :: CreateCall -> String
$cshow :: CreateCall -> String
showsPrec :: Int -> CreateCall -> ShowS
$cshowsPrec :: Int -> CreateCall -> ShowS
Show, CreateCall -> CreateCall -> Bool
(CreateCall -> CreateCall -> Bool)
-> (CreateCall -> CreateCall -> Bool) -> Eq CreateCall
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCall -> CreateCall -> Bool
$c/= :: CreateCall -> CreateCall -> Bool
== :: CreateCall -> CreateCall -> Bool
$c== :: CreateCall -> CreateCall -> Bool
Eq, (forall x. CreateCall -> Rep CreateCall x)
-> (forall x. Rep CreateCall x -> CreateCall) -> Generic CreateCall
forall x. Rep CreateCall x -> CreateCall
forall x. CreateCall -> Rep CreateCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateCall x -> CreateCall
$cfrom :: forall x. CreateCall -> Rep CreateCall x
Generic)

-- | Parameter of Function acceptCall
data AcceptCall
  = -- | Accepts an incoming call
    AcceptCall
      { -- | Call identifier
        AcceptCall -> Int
call_id :: I32,
        -- | Description of the call protocols supported by the client
        AcceptCall -> CallProtocol
protocol :: CallProtocol
      }
  deriving (Int -> AcceptCall -> ShowS
[AcceptCall] -> ShowS
AcceptCall -> String
(Int -> AcceptCall -> ShowS)
-> (AcceptCall -> String)
-> ([AcceptCall] -> ShowS)
-> Show AcceptCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptCall] -> ShowS
$cshowList :: [AcceptCall] -> ShowS
show :: AcceptCall -> String
$cshow :: AcceptCall -> String
showsPrec :: Int -> AcceptCall -> ShowS
$cshowsPrec :: Int -> AcceptCall -> ShowS
Show, AcceptCall -> AcceptCall -> Bool
(AcceptCall -> AcceptCall -> Bool)
-> (AcceptCall -> AcceptCall -> Bool) -> Eq AcceptCall
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptCall -> AcceptCall -> Bool
$c/= :: AcceptCall -> AcceptCall -> Bool
== :: AcceptCall -> AcceptCall -> Bool
$c== :: AcceptCall -> AcceptCall -> Bool
Eq, (forall x. AcceptCall -> Rep AcceptCall x)
-> (forall x. Rep AcceptCall x -> AcceptCall) -> Generic AcceptCall
forall x. Rep AcceptCall x -> AcceptCall
forall x. AcceptCall -> Rep AcceptCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AcceptCall x -> AcceptCall
$cfrom :: forall x. AcceptCall -> Rep AcceptCall x
Generic)

-- | Parameter of Function discardCall
data DiscardCall
  = -- | Discards a call
    DiscardCall
      { -- | Call identifier
        DiscardCall -> Int
call_id :: I32,
        -- | True, if the user was disconnected
        DiscardCall -> Bool
is_disconnected :: Bool,
        -- | The call duration, in seconds
        DiscardCall -> Int
duration :: I32,
        -- | Identifier of the connection used during the call
        DiscardCall -> I64
connection_id :: I64
      }
  deriving (Int -> DiscardCall -> ShowS
[DiscardCall] -> ShowS
DiscardCall -> String
(Int -> DiscardCall -> ShowS)
-> (DiscardCall -> String)
-> ([DiscardCall] -> ShowS)
-> Show DiscardCall
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DiscardCall] -> ShowS
$cshowList :: [DiscardCall] -> ShowS
show :: DiscardCall -> String
$cshow :: DiscardCall -> String
showsPrec :: Int -> DiscardCall -> ShowS
$cshowsPrec :: Int -> DiscardCall -> ShowS
Show, DiscardCall -> DiscardCall -> Bool
(DiscardCall -> DiscardCall -> Bool)
-> (DiscardCall -> DiscardCall -> Bool) -> Eq DiscardCall
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DiscardCall -> DiscardCall -> Bool
$c/= :: DiscardCall -> DiscardCall -> Bool
== :: DiscardCall -> DiscardCall -> Bool
$c== :: DiscardCall -> DiscardCall -> Bool
Eq, (forall x. DiscardCall -> Rep DiscardCall x)
-> (forall x. Rep DiscardCall x -> DiscardCall)
-> Generic DiscardCall
forall x. Rep DiscardCall x -> DiscardCall
forall x. DiscardCall -> Rep DiscardCall x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DiscardCall x -> DiscardCall
$cfrom :: forall x. DiscardCall -> Rep DiscardCall x
Generic)

-- | Parameter of Function sendCallRating
data SendCallRating
  = -- | Sends a call rating
    SendCallRating
      { -- | Call identifier
        SendCallRating -> Int
call_id :: I32,
        -- | Call rating; 1-5
        SendCallRating -> Int
rating :: I32,
        -- | An optional user comment if the rating is less than 5
        SendCallRating -> T
comment :: T,
        -- | List of the exact types of problems with the call, specified by the user
        SendCallRating -> [CallProblem]
problems :: ([]) (CallProblem)
      }
  deriving (Int -> SendCallRating -> ShowS
[SendCallRating] -> ShowS
SendCallRating -> String
(Int -> SendCallRating -> ShowS)
-> (SendCallRating -> String)
-> ([SendCallRating] -> ShowS)
-> Show SendCallRating
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendCallRating] -> ShowS
$cshowList :: [SendCallRating] -> ShowS
show :: SendCallRating -> String
$cshow :: SendCallRating -> String
showsPrec :: Int -> SendCallRating -> ShowS
$cshowsPrec :: Int -> SendCallRating -> ShowS
Show, SendCallRating -> SendCallRating -> Bool
(SendCallRating -> SendCallRating -> Bool)
-> (SendCallRating -> SendCallRating -> Bool) -> Eq SendCallRating
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendCallRating -> SendCallRating -> Bool
$c/= :: SendCallRating -> SendCallRating -> Bool
== :: SendCallRating -> SendCallRating -> Bool
$c== :: SendCallRating -> SendCallRating -> Bool
Eq, (forall x. SendCallRating -> Rep SendCallRating x)
-> (forall x. Rep SendCallRating x -> SendCallRating)
-> Generic SendCallRating
forall x. Rep SendCallRating x -> SendCallRating
forall x. SendCallRating -> Rep SendCallRating x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendCallRating x -> SendCallRating
$cfrom :: forall x. SendCallRating -> Rep SendCallRating x
Generic)

-- | Parameter of Function sendCallDebugInformation
data SendCallDebugInformation
  = -- | Sends debug information for a call
    SendCallDebugInformation
      { -- | Call identifier
        SendCallDebugInformation -> Int
call_id :: I32,
        -- | Debug information in application-specific format
        SendCallDebugInformation -> T
debug_information :: T
      }
  deriving (Int -> SendCallDebugInformation -> ShowS
[SendCallDebugInformation] -> ShowS
SendCallDebugInformation -> String
(Int -> SendCallDebugInformation -> ShowS)
-> (SendCallDebugInformation -> String)
-> ([SendCallDebugInformation] -> ShowS)
-> Show SendCallDebugInformation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendCallDebugInformation] -> ShowS
$cshowList :: [SendCallDebugInformation] -> ShowS
show :: SendCallDebugInformation -> String
$cshow :: SendCallDebugInformation -> String
showsPrec :: Int -> SendCallDebugInformation -> ShowS
$cshowsPrec :: Int -> SendCallDebugInformation -> ShowS
Show, SendCallDebugInformation -> SendCallDebugInformation -> Bool
(SendCallDebugInformation -> SendCallDebugInformation -> Bool)
-> (SendCallDebugInformation -> SendCallDebugInformation -> Bool)
-> Eq SendCallDebugInformation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendCallDebugInformation -> SendCallDebugInformation -> Bool
$c/= :: SendCallDebugInformation -> SendCallDebugInformation -> Bool
== :: SendCallDebugInformation -> SendCallDebugInformation -> Bool
$c== :: SendCallDebugInformation -> SendCallDebugInformation -> Bool
Eq, (forall x.
 SendCallDebugInformation -> Rep SendCallDebugInformation x)
-> (forall x.
    Rep SendCallDebugInformation x -> SendCallDebugInformation)
-> Generic SendCallDebugInformation
forall x.
Rep SendCallDebugInformation x -> SendCallDebugInformation
forall x.
SendCallDebugInformation -> Rep SendCallDebugInformation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendCallDebugInformation x -> SendCallDebugInformation
$cfrom :: forall x.
SendCallDebugInformation -> Rep SendCallDebugInformation x
Generic)

-- | Parameter of Function blockUser
data BlockUser
  = -- | Adds a user to the blacklist
    BlockUser
      { -- | User identifier
        BlockUser -> Int
user_id :: I32
      }
  deriving (Int -> BlockUser -> ShowS
[BlockUser] -> ShowS
BlockUser -> String
(Int -> BlockUser -> ShowS)
-> (BlockUser -> String)
-> ([BlockUser] -> ShowS)
-> Show BlockUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BlockUser] -> ShowS
$cshowList :: [BlockUser] -> ShowS
show :: BlockUser -> String
$cshow :: BlockUser -> String
showsPrec :: Int -> BlockUser -> ShowS
$cshowsPrec :: Int -> BlockUser -> ShowS
Show, BlockUser -> BlockUser -> Bool
(BlockUser -> BlockUser -> Bool)
-> (BlockUser -> BlockUser -> Bool) -> Eq BlockUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BlockUser -> BlockUser -> Bool
$c/= :: BlockUser -> BlockUser -> Bool
== :: BlockUser -> BlockUser -> Bool
$c== :: BlockUser -> BlockUser -> Bool
Eq, (forall x. BlockUser -> Rep BlockUser x)
-> (forall x. Rep BlockUser x -> BlockUser) -> Generic BlockUser
forall x. Rep BlockUser x -> BlockUser
forall x. BlockUser -> Rep BlockUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BlockUser x -> BlockUser
$cfrom :: forall x. BlockUser -> Rep BlockUser x
Generic)

-- | Parameter of Function unblockUser
data UnblockUser
  = -- | Removes a user from the blacklist
    UnblockUser
      { -- | User identifier
        UnblockUser -> Int
user_id :: I32
      }
  deriving (Int -> UnblockUser -> ShowS
[UnblockUser] -> ShowS
UnblockUser -> String
(Int -> UnblockUser -> ShowS)
-> (UnblockUser -> String)
-> ([UnblockUser] -> ShowS)
-> Show UnblockUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UnblockUser] -> ShowS
$cshowList :: [UnblockUser] -> ShowS
show :: UnblockUser -> String
$cshow :: UnblockUser -> String
showsPrec :: Int -> UnblockUser -> ShowS
$cshowsPrec :: Int -> UnblockUser -> ShowS
Show, UnblockUser -> UnblockUser -> Bool
(UnblockUser -> UnblockUser -> Bool)
-> (UnblockUser -> UnblockUser -> Bool) -> Eq UnblockUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnblockUser -> UnblockUser -> Bool
$c/= :: UnblockUser -> UnblockUser -> Bool
== :: UnblockUser -> UnblockUser -> Bool
$c== :: UnblockUser -> UnblockUser -> Bool
Eq, (forall x. UnblockUser -> Rep UnblockUser x)
-> (forall x. Rep UnblockUser x -> UnblockUser)
-> Generic UnblockUser
forall x. Rep UnblockUser x -> UnblockUser
forall x. UnblockUser -> Rep UnblockUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UnblockUser x -> UnblockUser
$cfrom :: forall x. UnblockUser -> Rep UnblockUser x
Generic)

-- | Parameter of Function getBlockedUsers
data GetBlockedUsers
  = -- | Returns users that were blocked by the current user
    GetBlockedUsers
      { -- | Number of users to skip in the result; must be non-negative
        GetBlockedUsers -> Int
offset :: I32,
        -- | The maximum number of users to return; up to 100
        GetBlockedUsers -> Int
limit :: I32
      }
  deriving (Int -> GetBlockedUsers -> ShowS
[GetBlockedUsers] -> ShowS
GetBlockedUsers -> String
(Int -> GetBlockedUsers -> ShowS)
-> (GetBlockedUsers -> String)
-> ([GetBlockedUsers] -> ShowS)
-> Show GetBlockedUsers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlockedUsers] -> ShowS
$cshowList :: [GetBlockedUsers] -> ShowS
show :: GetBlockedUsers -> String
$cshow :: GetBlockedUsers -> String
showsPrec :: Int -> GetBlockedUsers -> ShowS
$cshowsPrec :: Int -> GetBlockedUsers -> ShowS
Show, GetBlockedUsers -> GetBlockedUsers -> Bool
(GetBlockedUsers -> GetBlockedUsers -> Bool)
-> (GetBlockedUsers -> GetBlockedUsers -> Bool)
-> Eq GetBlockedUsers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlockedUsers -> GetBlockedUsers -> Bool
$c/= :: GetBlockedUsers -> GetBlockedUsers -> Bool
== :: GetBlockedUsers -> GetBlockedUsers -> Bool
$c== :: GetBlockedUsers -> GetBlockedUsers -> Bool
Eq, (forall x. GetBlockedUsers -> Rep GetBlockedUsers x)
-> (forall x. Rep GetBlockedUsers x -> GetBlockedUsers)
-> Generic GetBlockedUsers
forall x. Rep GetBlockedUsers x -> GetBlockedUsers
forall x. GetBlockedUsers -> Rep GetBlockedUsers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBlockedUsers x -> GetBlockedUsers
$cfrom :: forall x. GetBlockedUsers -> Rep GetBlockedUsers x
Generic)

-- | Parameter of Function addContact
data AddContact
  = -- | Adds a user to the contact list or edits an existing contact by their user identifier
    AddContact
      { -- | The contact to add or edit; phone number can be empty and needs to be specified only if known, vCard is ignored
        AddContact -> Contact
contact :: Contact,
        -- | True, if the new contact needs to be allowed to see current user's phone number. A corresponding rule to userPrivacySettingShowPhoneNumber will be added if needed. Use the field UserFullInfo.need_phone_number_privacy_exception to check whether the current user needs to be asked to share their phone number
        AddContact -> Bool
share_phone_number :: Bool
      }
  deriving (Int -> AddContact -> ShowS
[AddContact] -> ShowS
AddContact -> String
(Int -> AddContact -> ShowS)
-> (AddContact -> String)
-> ([AddContact] -> ShowS)
-> Show AddContact
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddContact] -> ShowS
$cshowList :: [AddContact] -> ShowS
show :: AddContact -> String
$cshow :: AddContact -> String
showsPrec :: Int -> AddContact -> ShowS
$cshowsPrec :: Int -> AddContact -> ShowS
Show, AddContact -> AddContact -> Bool
(AddContact -> AddContact -> Bool)
-> (AddContact -> AddContact -> Bool) -> Eq AddContact
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddContact -> AddContact -> Bool
$c/= :: AddContact -> AddContact -> Bool
== :: AddContact -> AddContact -> Bool
$c== :: AddContact -> AddContact -> Bool
Eq, (forall x. AddContact -> Rep AddContact x)
-> (forall x. Rep AddContact x -> AddContact) -> Generic AddContact
forall x. Rep AddContact x -> AddContact
forall x. AddContact -> Rep AddContact x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddContact x -> AddContact
$cfrom :: forall x. AddContact -> Rep AddContact x
Generic)

-- | Parameter of Function importContacts
data ImportContacts
  = -- | Adds new contacts or edits existing contacts by their phone numbers; contacts' user identifiers are ignored
    ImportContacts
      { -- | The list of contacts to import or edit; contacts' vCard are ignored and are not imported
        ImportContacts -> [Contact]
contacts :: ([]) (Contact)
      }
  deriving (Int -> ImportContacts -> ShowS
[ImportContacts] -> ShowS
ImportContacts -> String
(Int -> ImportContacts -> ShowS)
-> (ImportContacts -> String)
-> ([ImportContacts] -> ShowS)
-> Show ImportContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ImportContacts] -> ShowS
$cshowList :: [ImportContacts] -> ShowS
show :: ImportContacts -> String
$cshow :: ImportContacts -> String
showsPrec :: Int -> ImportContacts -> ShowS
$cshowsPrec :: Int -> ImportContacts -> ShowS
Show, ImportContacts -> ImportContacts -> Bool
(ImportContacts -> ImportContacts -> Bool)
-> (ImportContacts -> ImportContacts -> Bool) -> Eq ImportContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImportContacts -> ImportContacts -> Bool
$c/= :: ImportContacts -> ImportContacts -> Bool
== :: ImportContacts -> ImportContacts -> Bool
$c== :: ImportContacts -> ImportContacts -> Bool
Eq, (forall x. ImportContacts -> Rep ImportContacts x)
-> (forall x. Rep ImportContacts x -> ImportContacts)
-> Generic ImportContacts
forall x. Rep ImportContacts x -> ImportContacts
forall x. ImportContacts -> Rep ImportContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ImportContacts x -> ImportContacts
$cfrom :: forall x. ImportContacts -> Rep ImportContacts x
Generic)

-- | Parameter of Function getContacts
data GetContacts
  = -- | Returns all user contacts
    GetContacts
      {
      }
  deriving (Int -> GetContacts -> ShowS
[GetContacts] -> ShowS
GetContacts -> String
(Int -> GetContacts -> ShowS)
-> (GetContacts -> String)
-> ([GetContacts] -> ShowS)
-> Show GetContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetContacts] -> ShowS
$cshowList :: [GetContacts] -> ShowS
show :: GetContacts -> String
$cshow :: GetContacts -> String
showsPrec :: Int -> GetContacts -> ShowS
$cshowsPrec :: Int -> GetContacts -> ShowS
Show, GetContacts -> GetContacts -> Bool
(GetContacts -> GetContacts -> Bool)
-> (GetContacts -> GetContacts -> Bool) -> Eq GetContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetContacts -> GetContacts -> Bool
$c/= :: GetContacts -> GetContacts -> Bool
== :: GetContacts -> GetContacts -> Bool
$c== :: GetContacts -> GetContacts -> Bool
Eq, (forall x. GetContacts -> Rep GetContacts x)
-> (forall x. Rep GetContacts x -> GetContacts)
-> Generic GetContacts
forall x. Rep GetContacts x -> GetContacts
forall x. GetContacts -> Rep GetContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetContacts x -> GetContacts
$cfrom :: forall x. GetContacts -> Rep GetContacts x
Generic)

-- | Parameter of Function searchContacts
data SearchContacts
  = -- | Searches for the specified query in the first names, last names and usernames of the known user contacts
    SearchContacts
      { -- | Query to search for; may be empty to return all contacts
        SearchContacts -> T
query :: T,
        -- | The maximum number of users to be returned
        SearchContacts -> Int
limit :: I32
      }
  deriving (Int -> SearchContacts -> ShowS
[SearchContacts] -> ShowS
SearchContacts -> String
(Int -> SearchContacts -> ShowS)
-> (SearchContacts -> String)
-> ([SearchContacts] -> ShowS)
-> Show SearchContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchContacts] -> ShowS
$cshowList :: [SearchContacts] -> ShowS
show :: SearchContacts -> String
$cshow :: SearchContacts -> String
showsPrec :: Int -> SearchContacts -> ShowS
$cshowsPrec :: Int -> SearchContacts -> ShowS
Show, SearchContacts -> SearchContacts -> Bool
(SearchContacts -> SearchContacts -> Bool)
-> (SearchContacts -> SearchContacts -> Bool) -> Eq SearchContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchContacts -> SearchContacts -> Bool
$c/= :: SearchContacts -> SearchContacts -> Bool
== :: SearchContacts -> SearchContacts -> Bool
$c== :: SearchContacts -> SearchContacts -> Bool
Eq, (forall x. SearchContacts -> Rep SearchContacts x)
-> (forall x. Rep SearchContacts x -> SearchContacts)
-> Generic SearchContacts
forall x. Rep SearchContacts x -> SearchContacts
forall x. SearchContacts -> Rep SearchContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchContacts x -> SearchContacts
$cfrom :: forall x. SearchContacts -> Rep SearchContacts x
Generic)

-- | Parameter of Function removeContacts
data RemoveContacts
  = -- | Removes users from the contact list
    RemoveContacts
      { -- | Identifiers of users to be deleted
        RemoveContacts -> [Int]
user_ids :: ([]) (I32)
      }
  deriving (Int -> RemoveContacts -> ShowS
[RemoveContacts] -> ShowS
RemoveContacts -> String
(Int -> RemoveContacts -> ShowS)
-> (RemoveContacts -> String)
-> ([RemoveContacts] -> ShowS)
-> Show RemoveContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveContacts] -> ShowS
$cshowList :: [RemoveContacts] -> ShowS
show :: RemoveContacts -> String
$cshow :: RemoveContacts -> String
showsPrec :: Int -> RemoveContacts -> ShowS
$cshowsPrec :: Int -> RemoveContacts -> ShowS
Show, RemoveContacts -> RemoveContacts -> Bool
(RemoveContacts -> RemoveContacts -> Bool)
-> (RemoveContacts -> RemoveContacts -> Bool) -> Eq RemoveContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveContacts -> RemoveContacts -> Bool
$c/= :: RemoveContacts -> RemoveContacts -> Bool
== :: RemoveContacts -> RemoveContacts -> Bool
$c== :: RemoveContacts -> RemoveContacts -> Bool
Eq, (forall x. RemoveContacts -> Rep RemoveContacts x)
-> (forall x. Rep RemoveContacts x -> RemoveContacts)
-> Generic RemoveContacts
forall x. Rep RemoveContacts x -> RemoveContacts
forall x. RemoveContacts -> Rep RemoveContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveContacts x -> RemoveContacts
$cfrom :: forall x. RemoveContacts -> Rep RemoveContacts x
Generic)

-- | Parameter of Function getImportedContactCount
data GetImportedContactCount
  = -- | Returns the total number of imported contacts
    GetImportedContactCount
      {
      }
  deriving (Int -> GetImportedContactCount -> ShowS
[GetImportedContactCount] -> ShowS
GetImportedContactCount -> String
(Int -> GetImportedContactCount -> ShowS)
-> (GetImportedContactCount -> String)
-> ([GetImportedContactCount] -> ShowS)
-> Show GetImportedContactCount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetImportedContactCount] -> ShowS
$cshowList :: [GetImportedContactCount] -> ShowS
show :: GetImportedContactCount -> String
$cshow :: GetImportedContactCount -> String
showsPrec :: Int -> GetImportedContactCount -> ShowS
$cshowsPrec :: Int -> GetImportedContactCount -> ShowS
Show, GetImportedContactCount -> GetImportedContactCount -> Bool
(GetImportedContactCount -> GetImportedContactCount -> Bool)
-> (GetImportedContactCount -> GetImportedContactCount -> Bool)
-> Eq GetImportedContactCount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetImportedContactCount -> GetImportedContactCount -> Bool
$c/= :: GetImportedContactCount -> GetImportedContactCount -> Bool
== :: GetImportedContactCount -> GetImportedContactCount -> Bool
$c== :: GetImportedContactCount -> GetImportedContactCount -> Bool
Eq, (forall x.
 GetImportedContactCount -> Rep GetImportedContactCount x)
-> (forall x.
    Rep GetImportedContactCount x -> GetImportedContactCount)
-> Generic GetImportedContactCount
forall x. Rep GetImportedContactCount x -> GetImportedContactCount
forall x. GetImportedContactCount -> Rep GetImportedContactCount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetImportedContactCount x -> GetImportedContactCount
$cfrom :: forall x. GetImportedContactCount -> Rep GetImportedContactCount x
Generic)

-- | Parameter of Function changeImportedContacts
data ChangeImportedContacts
  = -- | Changes imported contacts using the list of current user contacts saved on the device. Imports newly added contacts and, if at least the file database is enabled, deletes recently deleted contacts.
    ChangeImportedContacts
      { ChangeImportedContacts -> [Contact]
contacts :: ([]) (Contact)
      }
  deriving (Int -> ChangeImportedContacts -> ShowS
[ChangeImportedContacts] -> ShowS
ChangeImportedContacts -> String
(Int -> ChangeImportedContacts -> ShowS)
-> (ChangeImportedContacts -> String)
-> ([ChangeImportedContacts] -> ShowS)
-> Show ChangeImportedContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeImportedContacts] -> ShowS
$cshowList :: [ChangeImportedContacts] -> ShowS
show :: ChangeImportedContacts -> String
$cshow :: ChangeImportedContacts -> String
showsPrec :: Int -> ChangeImportedContacts -> ShowS
$cshowsPrec :: Int -> ChangeImportedContacts -> ShowS
Show, ChangeImportedContacts -> ChangeImportedContacts -> Bool
(ChangeImportedContacts -> ChangeImportedContacts -> Bool)
-> (ChangeImportedContacts -> ChangeImportedContacts -> Bool)
-> Eq ChangeImportedContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeImportedContacts -> ChangeImportedContacts -> Bool
$c/= :: ChangeImportedContacts -> ChangeImportedContacts -> Bool
== :: ChangeImportedContacts -> ChangeImportedContacts -> Bool
$c== :: ChangeImportedContacts -> ChangeImportedContacts -> Bool
Eq, (forall x. ChangeImportedContacts -> Rep ChangeImportedContacts x)
-> (forall x.
    Rep ChangeImportedContacts x -> ChangeImportedContacts)
-> Generic ChangeImportedContacts
forall x. Rep ChangeImportedContacts x -> ChangeImportedContacts
forall x. ChangeImportedContacts -> Rep ChangeImportedContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangeImportedContacts x -> ChangeImportedContacts
$cfrom :: forall x. ChangeImportedContacts -> Rep ChangeImportedContacts x
Generic)

-- | Parameter of Function clearImportedContacts
data ClearImportedContacts
  = -- | Clears all imported contacts, contact list remains unchanged
    ClearImportedContacts
      {
      }
  deriving (Int -> ClearImportedContacts -> ShowS
[ClearImportedContacts] -> ShowS
ClearImportedContacts -> String
(Int -> ClearImportedContacts -> ShowS)
-> (ClearImportedContacts -> String)
-> ([ClearImportedContacts] -> ShowS)
-> Show ClearImportedContacts
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearImportedContacts] -> ShowS
$cshowList :: [ClearImportedContacts] -> ShowS
show :: ClearImportedContacts -> String
$cshow :: ClearImportedContacts -> String
showsPrec :: Int -> ClearImportedContacts -> ShowS
$cshowsPrec :: Int -> ClearImportedContacts -> ShowS
Show, ClearImportedContacts -> ClearImportedContacts -> Bool
(ClearImportedContacts -> ClearImportedContacts -> Bool)
-> (ClearImportedContacts -> ClearImportedContacts -> Bool)
-> Eq ClearImportedContacts
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearImportedContacts -> ClearImportedContacts -> Bool
$c/= :: ClearImportedContacts -> ClearImportedContacts -> Bool
== :: ClearImportedContacts -> ClearImportedContacts -> Bool
$c== :: ClearImportedContacts -> ClearImportedContacts -> Bool
Eq, (forall x. ClearImportedContacts -> Rep ClearImportedContacts x)
-> (forall x. Rep ClearImportedContacts x -> ClearImportedContacts)
-> Generic ClearImportedContacts
forall x. Rep ClearImportedContacts x -> ClearImportedContacts
forall x. ClearImportedContacts -> Rep ClearImportedContacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClearImportedContacts x -> ClearImportedContacts
$cfrom :: forall x. ClearImportedContacts -> Rep ClearImportedContacts x
Generic)

-- | Parameter of Function sharePhoneNumber
data SharePhoneNumber
  = -- | Shares the phone number of the current user with a mutual contact. Supposed to be called when the user clicks on chatActionBarSharePhoneNumber
    SharePhoneNumber
      { -- | Identifier of the user with whom to share the phone number. The user must be a mutual contact
        SharePhoneNumber -> Int
user_id :: I32
      }
  deriving (Int -> SharePhoneNumber -> ShowS
[SharePhoneNumber] -> ShowS
SharePhoneNumber -> String
(Int -> SharePhoneNumber -> ShowS)
-> (SharePhoneNumber -> String)
-> ([SharePhoneNumber] -> ShowS)
-> Show SharePhoneNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SharePhoneNumber] -> ShowS
$cshowList :: [SharePhoneNumber] -> ShowS
show :: SharePhoneNumber -> String
$cshow :: SharePhoneNumber -> String
showsPrec :: Int -> SharePhoneNumber -> ShowS
$cshowsPrec :: Int -> SharePhoneNumber -> ShowS
Show, SharePhoneNumber -> SharePhoneNumber -> Bool
(SharePhoneNumber -> SharePhoneNumber -> Bool)
-> (SharePhoneNumber -> SharePhoneNumber -> Bool)
-> Eq SharePhoneNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SharePhoneNumber -> SharePhoneNumber -> Bool
$c/= :: SharePhoneNumber -> SharePhoneNumber -> Bool
== :: SharePhoneNumber -> SharePhoneNumber -> Bool
$c== :: SharePhoneNumber -> SharePhoneNumber -> Bool
Eq, (forall x. SharePhoneNumber -> Rep SharePhoneNumber x)
-> (forall x. Rep SharePhoneNumber x -> SharePhoneNumber)
-> Generic SharePhoneNumber
forall x. Rep SharePhoneNumber x -> SharePhoneNumber
forall x. SharePhoneNumber -> Rep SharePhoneNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SharePhoneNumber x -> SharePhoneNumber
$cfrom :: forall x. SharePhoneNumber -> Rep SharePhoneNumber x
Generic)

-- | Parameter of Function getUserProfilePhotos
data GetUserProfilePhotos
  = -- | Returns the profile photos of a user. The result of this query may be outdated: some photos might have been deleted already
    GetUserProfilePhotos
      { -- | User identifier
        GetUserProfilePhotos -> Int
user_id :: I32,
        -- | The number of photos to skip; must be non-negative
        GetUserProfilePhotos -> Int
offset :: I32,
        -- | The maximum number of photos to be returned; up to 100
        GetUserProfilePhotos -> Int
limit :: I32
      }
  deriving (Int -> GetUserProfilePhotos -> ShowS
[GetUserProfilePhotos] -> ShowS
GetUserProfilePhotos -> String
(Int -> GetUserProfilePhotos -> ShowS)
-> (GetUserProfilePhotos -> String)
-> ([GetUserProfilePhotos] -> ShowS)
-> Show GetUserProfilePhotos
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUserProfilePhotos] -> ShowS
$cshowList :: [GetUserProfilePhotos] -> ShowS
show :: GetUserProfilePhotos -> String
$cshow :: GetUserProfilePhotos -> String
showsPrec :: Int -> GetUserProfilePhotos -> ShowS
$cshowsPrec :: Int -> GetUserProfilePhotos -> ShowS
Show, GetUserProfilePhotos -> GetUserProfilePhotos -> Bool
(GetUserProfilePhotos -> GetUserProfilePhotos -> Bool)
-> (GetUserProfilePhotos -> GetUserProfilePhotos -> Bool)
-> Eq GetUserProfilePhotos
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUserProfilePhotos -> GetUserProfilePhotos -> Bool
$c/= :: GetUserProfilePhotos -> GetUserProfilePhotos -> Bool
== :: GetUserProfilePhotos -> GetUserProfilePhotos -> Bool
$c== :: GetUserProfilePhotos -> GetUserProfilePhotos -> Bool
Eq, (forall x. GetUserProfilePhotos -> Rep GetUserProfilePhotos x)
-> (forall x. Rep GetUserProfilePhotos x -> GetUserProfilePhotos)
-> Generic GetUserProfilePhotos
forall x. Rep GetUserProfilePhotos x -> GetUserProfilePhotos
forall x. GetUserProfilePhotos -> Rep GetUserProfilePhotos x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetUserProfilePhotos x -> GetUserProfilePhotos
$cfrom :: forall x. GetUserProfilePhotos -> Rep GetUserProfilePhotos x
Generic)

-- | Parameter of Function getStickers
data GetStickers
  = -- | Returns stickers from the installed sticker sets that correspond to a given emoji. If the emoji is not empty, favorite and recently used stickers may also be returned
    GetStickers
      { -- | String representation of emoji. If empty, returns all known installed stickers
        GetStickers -> T
emoji :: T,
        -- | The maximum number of stickers to be returned
        GetStickers -> Int
limit :: I32
      }
  deriving (Int -> GetStickers -> ShowS
[GetStickers] -> ShowS
GetStickers -> String
(Int -> GetStickers -> ShowS)
-> (GetStickers -> String)
-> ([GetStickers] -> ShowS)
-> Show GetStickers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStickers] -> ShowS
$cshowList :: [GetStickers] -> ShowS
show :: GetStickers -> String
$cshow :: GetStickers -> String
showsPrec :: Int -> GetStickers -> ShowS
$cshowsPrec :: Int -> GetStickers -> ShowS
Show, GetStickers -> GetStickers -> Bool
(GetStickers -> GetStickers -> Bool)
-> (GetStickers -> GetStickers -> Bool) -> Eq GetStickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStickers -> GetStickers -> Bool
$c/= :: GetStickers -> GetStickers -> Bool
== :: GetStickers -> GetStickers -> Bool
$c== :: GetStickers -> GetStickers -> Bool
Eq, (forall x. GetStickers -> Rep GetStickers x)
-> (forall x. Rep GetStickers x -> GetStickers)
-> Generic GetStickers
forall x. Rep GetStickers x -> GetStickers
forall x. GetStickers -> Rep GetStickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetStickers x -> GetStickers
$cfrom :: forall x. GetStickers -> Rep GetStickers x
Generic)

-- | Parameter of Function searchStickers
data SearchStickers
  = -- | Searches for stickers from public sticker sets that correspond to a given emoji
    SearchStickers
      { -- | String representation of emoji; must be non-empty
        SearchStickers -> T
emoji :: T,
        -- | The maximum number of stickers to be returned
        SearchStickers -> Int
limit :: I32
      }
  deriving (Int -> SearchStickers -> ShowS
[SearchStickers] -> ShowS
SearchStickers -> String
(Int -> SearchStickers -> ShowS)
-> (SearchStickers -> String)
-> ([SearchStickers] -> ShowS)
-> Show SearchStickers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchStickers] -> ShowS
$cshowList :: [SearchStickers] -> ShowS
show :: SearchStickers -> String
$cshow :: SearchStickers -> String
showsPrec :: Int -> SearchStickers -> ShowS
$cshowsPrec :: Int -> SearchStickers -> ShowS
Show, SearchStickers -> SearchStickers -> Bool
(SearchStickers -> SearchStickers -> Bool)
-> (SearchStickers -> SearchStickers -> Bool) -> Eq SearchStickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchStickers -> SearchStickers -> Bool
$c/= :: SearchStickers -> SearchStickers -> Bool
== :: SearchStickers -> SearchStickers -> Bool
$c== :: SearchStickers -> SearchStickers -> Bool
Eq, (forall x. SearchStickers -> Rep SearchStickers x)
-> (forall x. Rep SearchStickers x -> SearchStickers)
-> Generic SearchStickers
forall x. Rep SearchStickers x -> SearchStickers
forall x. SearchStickers -> Rep SearchStickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchStickers x -> SearchStickers
$cfrom :: forall x. SearchStickers -> Rep SearchStickers x
Generic)

-- | Parameter of Function getInstalledStickerSets
data GetInstalledStickerSets
  = -- | Returns a list of installed sticker sets
    GetInstalledStickerSets
      { -- | Pass true to return mask sticker sets; pass false to return ordinary sticker sets
        GetInstalledStickerSets -> Bool
is_masks :: Bool
      }
  deriving (Int -> GetInstalledStickerSets -> ShowS
[GetInstalledStickerSets] -> ShowS
GetInstalledStickerSets -> String
(Int -> GetInstalledStickerSets -> ShowS)
-> (GetInstalledStickerSets -> String)
-> ([GetInstalledStickerSets] -> ShowS)
-> Show GetInstalledStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInstalledStickerSets] -> ShowS
$cshowList :: [GetInstalledStickerSets] -> ShowS
show :: GetInstalledStickerSets -> String
$cshow :: GetInstalledStickerSets -> String
showsPrec :: Int -> GetInstalledStickerSets -> ShowS
$cshowsPrec :: Int -> GetInstalledStickerSets -> ShowS
Show, GetInstalledStickerSets -> GetInstalledStickerSets -> Bool
(GetInstalledStickerSets -> GetInstalledStickerSets -> Bool)
-> (GetInstalledStickerSets -> GetInstalledStickerSets -> Bool)
-> Eq GetInstalledStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInstalledStickerSets -> GetInstalledStickerSets -> Bool
$c/= :: GetInstalledStickerSets -> GetInstalledStickerSets -> Bool
== :: GetInstalledStickerSets -> GetInstalledStickerSets -> Bool
$c== :: GetInstalledStickerSets -> GetInstalledStickerSets -> Bool
Eq, (forall x.
 GetInstalledStickerSets -> Rep GetInstalledStickerSets x)
-> (forall x.
    Rep GetInstalledStickerSets x -> GetInstalledStickerSets)
-> Generic GetInstalledStickerSets
forall x. Rep GetInstalledStickerSets x -> GetInstalledStickerSets
forall x. GetInstalledStickerSets -> Rep GetInstalledStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInstalledStickerSets x -> GetInstalledStickerSets
$cfrom :: forall x. GetInstalledStickerSets -> Rep GetInstalledStickerSets x
Generic)

-- | Parameter of Function getArchivedStickerSets
data GetArchivedStickerSets
  = -- | Returns a list of archived sticker sets
    GetArchivedStickerSets
      { -- | Pass true to return mask stickers sets; pass false to return ordinary sticker sets
        GetArchivedStickerSets -> Bool
is_masks :: Bool,
        -- | Identifier of the sticker set from which to return the result
        GetArchivedStickerSets -> I64
offset_sticker_set_id :: I64,
        -- | The maximum number of sticker sets to return
        GetArchivedStickerSets -> Int
limit :: I32
      }
  deriving (Int -> GetArchivedStickerSets -> ShowS
[GetArchivedStickerSets] -> ShowS
GetArchivedStickerSets -> String
(Int -> GetArchivedStickerSets -> ShowS)
-> (GetArchivedStickerSets -> String)
-> ([GetArchivedStickerSets] -> ShowS)
-> Show GetArchivedStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetArchivedStickerSets] -> ShowS
$cshowList :: [GetArchivedStickerSets] -> ShowS
show :: GetArchivedStickerSets -> String
$cshow :: GetArchivedStickerSets -> String
showsPrec :: Int -> GetArchivedStickerSets -> ShowS
$cshowsPrec :: Int -> GetArchivedStickerSets -> ShowS
Show, GetArchivedStickerSets -> GetArchivedStickerSets -> Bool
(GetArchivedStickerSets -> GetArchivedStickerSets -> Bool)
-> (GetArchivedStickerSets -> GetArchivedStickerSets -> Bool)
-> Eq GetArchivedStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetArchivedStickerSets -> GetArchivedStickerSets -> Bool
$c/= :: GetArchivedStickerSets -> GetArchivedStickerSets -> Bool
== :: GetArchivedStickerSets -> GetArchivedStickerSets -> Bool
$c== :: GetArchivedStickerSets -> GetArchivedStickerSets -> Bool
Eq, (forall x. GetArchivedStickerSets -> Rep GetArchivedStickerSets x)
-> (forall x.
    Rep GetArchivedStickerSets x -> GetArchivedStickerSets)
-> Generic GetArchivedStickerSets
forall x. Rep GetArchivedStickerSets x -> GetArchivedStickerSets
forall x. GetArchivedStickerSets -> Rep GetArchivedStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetArchivedStickerSets x -> GetArchivedStickerSets
$cfrom :: forall x. GetArchivedStickerSets -> Rep GetArchivedStickerSets x
Generic)

-- | Parameter of Function getTrendingStickerSets
data GetTrendingStickerSets
  = -- | Returns a list of trending sticker sets. For the optimal performance the number of returned sticker sets is chosen by the library
    GetTrendingStickerSets
      { -- | The offset from which to return the sticker sets; must be non-negative
        GetTrendingStickerSets -> Int
offset :: I32,
        -- | The maximum number of sticker sets to be returned; must be non-negative. Fewer sticker sets may be returned than specified by the limit, even if the end of the list has not been reached
        GetTrendingStickerSets -> Int
limit :: I32
      }
  deriving (Int -> GetTrendingStickerSets -> ShowS
[GetTrendingStickerSets] -> ShowS
GetTrendingStickerSets -> String
(Int -> GetTrendingStickerSets -> ShowS)
-> (GetTrendingStickerSets -> String)
-> ([GetTrendingStickerSets] -> ShowS)
-> Show GetTrendingStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetTrendingStickerSets] -> ShowS
$cshowList :: [GetTrendingStickerSets] -> ShowS
show :: GetTrendingStickerSets -> String
$cshow :: GetTrendingStickerSets -> String
showsPrec :: Int -> GetTrendingStickerSets -> ShowS
$cshowsPrec :: Int -> GetTrendingStickerSets -> ShowS
Show, GetTrendingStickerSets -> GetTrendingStickerSets -> Bool
(GetTrendingStickerSets -> GetTrendingStickerSets -> Bool)
-> (GetTrendingStickerSets -> GetTrendingStickerSets -> Bool)
-> Eq GetTrendingStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetTrendingStickerSets -> GetTrendingStickerSets -> Bool
$c/= :: GetTrendingStickerSets -> GetTrendingStickerSets -> Bool
== :: GetTrendingStickerSets -> GetTrendingStickerSets -> Bool
$c== :: GetTrendingStickerSets -> GetTrendingStickerSets -> Bool
Eq, (forall x. GetTrendingStickerSets -> Rep GetTrendingStickerSets x)
-> (forall x.
    Rep GetTrendingStickerSets x -> GetTrendingStickerSets)
-> Generic GetTrendingStickerSets
forall x. Rep GetTrendingStickerSets x -> GetTrendingStickerSets
forall x. GetTrendingStickerSets -> Rep GetTrendingStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetTrendingStickerSets x -> GetTrendingStickerSets
$cfrom :: forall x. GetTrendingStickerSets -> Rep GetTrendingStickerSets x
Generic)

-- | Parameter of Function getAttachedStickerSets
data GetAttachedStickerSets
  = -- | Returns a list of sticker sets attached to a file. Currently only photos and videos can have attached sticker sets
    GetAttachedStickerSets
      { -- | File identifier
        GetAttachedStickerSets -> Int
file_id :: I32
      }
  deriving (Int -> GetAttachedStickerSets -> ShowS
[GetAttachedStickerSets] -> ShowS
GetAttachedStickerSets -> String
(Int -> GetAttachedStickerSets -> ShowS)
-> (GetAttachedStickerSets -> String)
-> ([GetAttachedStickerSets] -> ShowS)
-> Show GetAttachedStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAttachedStickerSets] -> ShowS
$cshowList :: [GetAttachedStickerSets] -> ShowS
show :: GetAttachedStickerSets -> String
$cshow :: GetAttachedStickerSets -> String
showsPrec :: Int -> GetAttachedStickerSets -> ShowS
$cshowsPrec :: Int -> GetAttachedStickerSets -> ShowS
Show, GetAttachedStickerSets -> GetAttachedStickerSets -> Bool
(GetAttachedStickerSets -> GetAttachedStickerSets -> Bool)
-> (GetAttachedStickerSets -> GetAttachedStickerSets -> Bool)
-> Eq GetAttachedStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAttachedStickerSets -> GetAttachedStickerSets -> Bool
$c/= :: GetAttachedStickerSets -> GetAttachedStickerSets -> Bool
== :: GetAttachedStickerSets -> GetAttachedStickerSets -> Bool
$c== :: GetAttachedStickerSets -> GetAttachedStickerSets -> Bool
Eq, (forall x. GetAttachedStickerSets -> Rep GetAttachedStickerSets x)
-> (forall x.
    Rep GetAttachedStickerSets x -> GetAttachedStickerSets)
-> Generic GetAttachedStickerSets
forall x. Rep GetAttachedStickerSets x -> GetAttachedStickerSets
forall x. GetAttachedStickerSets -> Rep GetAttachedStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAttachedStickerSets x -> GetAttachedStickerSets
$cfrom :: forall x. GetAttachedStickerSets -> Rep GetAttachedStickerSets x
Generic)

-- | Parameter of Function getStickerSet
data GetStickerSet
  = -- | Returns information about a sticker set by its identifier
    GetStickerSet
      { -- | Identifier of the sticker set
        GetStickerSet -> I64
set_id :: I64
      }
  deriving (Int -> GetStickerSet -> ShowS
[GetStickerSet] -> ShowS
GetStickerSet -> String
(Int -> GetStickerSet -> ShowS)
-> (GetStickerSet -> String)
-> ([GetStickerSet] -> ShowS)
-> Show GetStickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStickerSet] -> ShowS
$cshowList :: [GetStickerSet] -> ShowS
show :: GetStickerSet -> String
$cshow :: GetStickerSet -> String
showsPrec :: Int -> GetStickerSet -> ShowS
$cshowsPrec :: Int -> GetStickerSet -> ShowS
Show, GetStickerSet -> GetStickerSet -> Bool
(GetStickerSet -> GetStickerSet -> Bool)
-> (GetStickerSet -> GetStickerSet -> Bool) -> Eq GetStickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStickerSet -> GetStickerSet -> Bool
$c/= :: GetStickerSet -> GetStickerSet -> Bool
== :: GetStickerSet -> GetStickerSet -> Bool
$c== :: GetStickerSet -> GetStickerSet -> Bool
Eq, (forall x. GetStickerSet -> Rep GetStickerSet x)
-> (forall x. Rep GetStickerSet x -> GetStickerSet)
-> Generic GetStickerSet
forall x. Rep GetStickerSet x -> GetStickerSet
forall x. GetStickerSet -> Rep GetStickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetStickerSet x -> GetStickerSet
$cfrom :: forall x. GetStickerSet -> Rep GetStickerSet x
Generic)

-- | Parameter of Function searchStickerSet
data SearchStickerSet
  = -- | Searches for a sticker set by its name
    SearchStickerSet
      { -- | Name of the sticker set
        SearchStickerSet -> T
name :: T
      }
  deriving (Int -> SearchStickerSet -> ShowS
[SearchStickerSet] -> ShowS
SearchStickerSet -> String
(Int -> SearchStickerSet -> ShowS)
-> (SearchStickerSet -> String)
-> ([SearchStickerSet] -> ShowS)
-> Show SearchStickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchStickerSet] -> ShowS
$cshowList :: [SearchStickerSet] -> ShowS
show :: SearchStickerSet -> String
$cshow :: SearchStickerSet -> String
showsPrec :: Int -> SearchStickerSet -> ShowS
$cshowsPrec :: Int -> SearchStickerSet -> ShowS
Show, SearchStickerSet -> SearchStickerSet -> Bool
(SearchStickerSet -> SearchStickerSet -> Bool)
-> (SearchStickerSet -> SearchStickerSet -> Bool)
-> Eq SearchStickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchStickerSet -> SearchStickerSet -> Bool
$c/= :: SearchStickerSet -> SearchStickerSet -> Bool
== :: SearchStickerSet -> SearchStickerSet -> Bool
$c== :: SearchStickerSet -> SearchStickerSet -> Bool
Eq, (forall x. SearchStickerSet -> Rep SearchStickerSet x)
-> (forall x. Rep SearchStickerSet x -> SearchStickerSet)
-> Generic SearchStickerSet
forall x. Rep SearchStickerSet x -> SearchStickerSet
forall x. SearchStickerSet -> Rep SearchStickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchStickerSet x -> SearchStickerSet
$cfrom :: forall x. SearchStickerSet -> Rep SearchStickerSet x
Generic)

-- | Parameter of Function searchInstalledStickerSets
data SearchInstalledStickerSets
  = -- | Searches for installed sticker sets by looking for specified query in their title and name
    SearchInstalledStickerSets
      { -- | Pass true to return mask sticker sets; pass false to return ordinary sticker sets
        SearchInstalledStickerSets -> Bool
is_masks :: Bool,
        -- | Query to search for
        SearchInstalledStickerSets -> T
query :: T,
        -- | The maximum number of sticker sets to return
        SearchInstalledStickerSets -> Int
limit :: I32
      }
  deriving (Int -> SearchInstalledStickerSets -> ShowS
[SearchInstalledStickerSets] -> ShowS
SearchInstalledStickerSets -> String
(Int -> SearchInstalledStickerSets -> ShowS)
-> (SearchInstalledStickerSets -> String)
-> ([SearchInstalledStickerSets] -> ShowS)
-> Show SearchInstalledStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchInstalledStickerSets] -> ShowS
$cshowList :: [SearchInstalledStickerSets] -> ShowS
show :: SearchInstalledStickerSets -> String
$cshow :: SearchInstalledStickerSets -> String
showsPrec :: Int -> SearchInstalledStickerSets -> ShowS
$cshowsPrec :: Int -> SearchInstalledStickerSets -> ShowS
Show, SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool
(SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool)
-> (SearchInstalledStickerSets
    -> SearchInstalledStickerSets -> Bool)
-> Eq SearchInstalledStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool
$c/= :: SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool
== :: SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool
$c== :: SearchInstalledStickerSets -> SearchInstalledStickerSets -> Bool
Eq, (forall x.
 SearchInstalledStickerSets -> Rep SearchInstalledStickerSets x)
-> (forall x.
    Rep SearchInstalledStickerSets x -> SearchInstalledStickerSets)
-> Generic SearchInstalledStickerSets
forall x.
Rep SearchInstalledStickerSets x -> SearchInstalledStickerSets
forall x.
SearchInstalledStickerSets -> Rep SearchInstalledStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SearchInstalledStickerSets x -> SearchInstalledStickerSets
$cfrom :: forall x.
SearchInstalledStickerSets -> Rep SearchInstalledStickerSets x
Generic)

-- | Parameter of Function searchStickerSets
data SearchStickerSets
  = -- | Searches for ordinary sticker sets by looking for specified query in their title and name. Excludes installed sticker sets from the results
    SearchStickerSets
      { -- | Query to search for
        SearchStickerSets -> T
query :: T
      }
  deriving (Int -> SearchStickerSets -> ShowS
[SearchStickerSets] -> ShowS
SearchStickerSets -> String
(Int -> SearchStickerSets -> ShowS)
-> (SearchStickerSets -> String)
-> ([SearchStickerSets] -> ShowS)
-> Show SearchStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchStickerSets] -> ShowS
$cshowList :: [SearchStickerSets] -> ShowS
show :: SearchStickerSets -> String
$cshow :: SearchStickerSets -> String
showsPrec :: Int -> SearchStickerSets -> ShowS
$cshowsPrec :: Int -> SearchStickerSets -> ShowS
Show, SearchStickerSets -> SearchStickerSets -> Bool
(SearchStickerSets -> SearchStickerSets -> Bool)
-> (SearchStickerSets -> SearchStickerSets -> Bool)
-> Eq SearchStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchStickerSets -> SearchStickerSets -> Bool
$c/= :: SearchStickerSets -> SearchStickerSets -> Bool
== :: SearchStickerSets -> SearchStickerSets -> Bool
$c== :: SearchStickerSets -> SearchStickerSets -> Bool
Eq, (forall x. SearchStickerSets -> Rep SearchStickerSets x)
-> (forall x. Rep SearchStickerSets x -> SearchStickerSets)
-> Generic SearchStickerSets
forall x. Rep SearchStickerSets x -> SearchStickerSets
forall x. SearchStickerSets -> Rep SearchStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchStickerSets x -> SearchStickerSets
$cfrom :: forall x. SearchStickerSets -> Rep SearchStickerSets x
Generic)

-- | Parameter of Function changeStickerSet
data ChangeStickerSet
  = -- | Installs/uninstalls or activates/archives a sticker set
    ChangeStickerSet
      { -- | Identifier of the sticker set
        ChangeStickerSet -> I64
set_id :: I64,
        -- | The new value of is_installed
        ChangeStickerSet -> Bool
is_installed :: Bool,
        -- | The new value of is_archived. A sticker set can't be installed and archived simultaneously
        ChangeStickerSet -> Bool
is_archived :: Bool
      }
  deriving (Int -> ChangeStickerSet -> ShowS
[ChangeStickerSet] -> ShowS
ChangeStickerSet -> String
(Int -> ChangeStickerSet -> ShowS)
-> (ChangeStickerSet -> String)
-> ([ChangeStickerSet] -> ShowS)
-> Show ChangeStickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangeStickerSet] -> ShowS
$cshowList :: [ChangeStickerSet] -> ShowS
show :: ChangeStickerSet -> String
$cshow :: ChangeStickerSet -> String
showsPrec :: Int -> ChangeStickerSet -> ShowS
$cshowsPrec :: Int -> ChangeStickerSet -> ShowS
Show, ChangeStickerSet -> ChangeStickerSet -> Bool
(ChangeStickerSet -> ChangeStickerSet -> Bool)
-> (ChangeStickerSet -> ChangeStickerSet -> Bool)
-> Eq ChangeStickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangeStickerSet -> ChangeStickerSet -> Bool
$c/= :: ChangeStickerSet -> ChangeStickerSet -> Bool
== :: ChangeStickerSet -> ChangeStickerSet -> Bool
$c== :: ChangeStickerSet -> ChangeStickerSet -> Bool
Eq, (forall x. ChangeStickerSet -> Rep ChangeStickerSet x)
-> (forall x. Rep ChangeStickerSet x -> ChangeStickerSet)
-> Generic ChangeStickerSet
forall x. Rep ChangeStickerSet x -> ChangeStickerSet
forall x. ChangeStickerSet -> Rep ChangeStickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangeStickerSet x -> ChangeStickerSet
$cfrom :: forall x. ChangeStickerSet -> Rep ChangeStickerSet x
Generic)

-- | Parameter of Function viewTrendingStickerSets
data ViewTrendingStickerSets
  = -- | Informs the server that some trending sticker sets have been viewed by the user
    ViewTrendingStickerSets
      { -- | Identifiers of viewed trending sticker sets
        ViewTrendingStickerSets -> [I64]
sticker_set_ids :: ([]) (I64)
      }
  deriving (Int -> ViewTrendingStickerSets -> ShowS
[ViewTrendingStickerSets] -> ShowS
ViewTrendingStickerSets -> String
(Int -> ViewTrendingStickerSets -> ShowS)
-> (ViewTrendingStickerSets -> String)
-> ([ViewTrendingStickerSets] -> ShowS)
-> Show ViewTrendingStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ViewTrendingStickerSets] -> ShowS
$cshowList :: [ViewTrendingStickerSets] -> ShowS
show :: ViewTrendingStickerSets -> String
$cshow :: ViewTrendingStickerSets -> String
showsPrec :: Int -> ViewTrendingStickerSets -> ShowS
$cshowsPrec :: Int -> ViewTrendingStickerSets -> ShowS
Show, ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool
(ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool)
-> (ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool)
-> Eq ViewTrendingStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool
$c/= :: ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool
== :: ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool
$c== :: ViewTrendingStickerSets -> ViewTrendingStickerSets -> Bool
Eq, (forall x.
 ViewTrendingStickerSets -> Rep ViewTrendingStickerSets x)
-> (forall x.
    Rep ViewTrendingStickerSets x -> ViewTrendingStickerSets)
-> Generic ViewTrendingStickerSets
forall x. Rep ViewTrendingStickerSets x -> ViewTrendingStickerSets
forall x. ViewTrendingStickerSets -> Rep ViewTrendingStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ViewTrendingStickerSets x -> ViewTrendingStickerSets
$cfrom :: forall x. ViewTrendingStickerSets -> Rep ViewTrendingStickerSets x
Generic)

-- | Parameter of Function reorderInstalledStickerSets
data ReorderInstalledStickerSets
  = -- | Changes the order of installed sticker sets
    ReorderInstalledStickerSets
      { -- | Pass true to change the order of mask sticker sets; pass false to change the order of ordinary sticker sets
        ReorderInstalledStickerSets -> Bool
is_masks :: Bool,
        -- | Identifiers of installed sticker sets in the new correct order
        ReorderInstalledStickerSets -> [I64]
sticker_set_ids :: ([]) (I64)
      }
  deriving (Int -> ReorderInstalledStickerSets -> ShowS
[ReorderInstalledStickerSets] -> ShowS
ReorderInstalledStickerSets -> String
(Int -> ReorderInstalledStickerSets -> ShowS)
-> (ReorderInstalledStickerSets -> String)
-> ([ReorderInstalledStickerSets] -> ShowS)
-> Show ReorderInstalledStickerSets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReorderInstalledStickerSets] -> ShowS
$cshowList :: [ReorderInstalledStickerSets] -> ShowS
show :: ReorderInstalledStickerSets -> String
$cshow :: ReorderInstalledStickerSets -> String
showsPrec :: Int -> ReorderInstalledStickerSets -> ShowS
$cshowsPrec :: Int -> ReorderInstalledStickerSets -> ShowS
Show, ReorderInstalledStickerSets -> ReorderInstalledStickerSets -> Bool
(ReorderInstalledStickerSets
 -> ReorderInstalledStickerSets -> Bool)
-> (ReorderInstalledStickerSets
    -> ReorderInstalledStickerSets -> Bool)
-> Eq ReorderInstalledStickerSets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReorderInstalledStickerSets -> ReorderInstalledStickerSets -> Bool
$c/= :: ReorderInstalledStickerSets -> ReorderInstalledStickerSets -> Bool
== :: ReorderInstalledStickerSets -> ReorderInstalledStickerSets -> Bool
$c== :: ReorderInstalledStickerSets -> ReorderInstalledStickerSets -> Bool
Eq, (forall x.
 ReorderInstalledStickerSets -> Rep ReorderInstalledStickerSets x)
-> (forall x.
    Rep ReorderInstalledStickerSets x -> ReorderInstalledStickerSets)
-> Generic ReorderInstalledStickerSets
forall x.
Rep ReorderInstalledStickerSets x -> ReorderInstalledStickerSets
forall x.
ReorderInstalledStickerSets -> Rep ReorderInstalledStickerSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ReorderInstalledStickerSets x -> ReorderInstalledStickerSets
$cfrom :: forall x.
ReorderInstalledStickerSets -> Rep ReorderInstalledStickerSets x
Generic)

-- | Parameter of Function getRecentStickers
data GetRecentStickers
  = -- | Returns a list of recently used stickers
    GetRecentStickers
      { -- | Pass true to return stickers and masks that were recently attached to photos or video files; pass false to return recently sent stickers
        GetRecentStickers -> Bool
is_attached :: Bool
      }
  deriving (Int -> GetRecentStickers -> ShowS
[GetRecentStickers] -> ShowS
GetRecentStickers -> String
(Int -> GetRecentStickers -> ShowS)
-> (GetRecentStickers -> String)
-> ([GetRecentStickers] -> ShowS)
-> Show GetRecentStickers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecentStickers] -> ShowS
$cshowList :: [GetRecentStickers] -> ShowS
show :: GetRecentStickers -> String
$cshow :: GetRecentStickers -> String
showsPrec :: Int -> GetRecentStickers -> ShowS
$cshowsPrec :: Int -> GetRecentStickers -> ShowS
Show, GetRecentStickers -> GetRecentStickers -> Bool
(GetRecentStickers -> GetRecentStickers -> Bool)
-> (GetRecentStickers -> GetRecentStickers -> Bool)
-> Eq GetRecentStickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecentStickers -> GetRecentStickers -> Bool
$c/= :: GetRecentStickers -> GetRecentStickers -> Bool
== :: GetRecentStickers -> GetRecentStickers -> Bool
$c== :: GetRecentStickers -> GetRecentStickers -> Bool
Eq, (forall x. GetRecentStickers -> Rep GetRecentStickers x)
-> (forall x. Rep GetRecentStickers x -> GetRecentStickers)
-> Generic GetRecentStickers
forall x. Rep GetRecentStickers x -> GetRecentStickers
forall x. GetRecentStickers -> Rep GetRecentStickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRecentStickers x -> GetRecentStickers
$cfrom :: forall x. GetRecentStickers -> Rep GetRecentStickers x
Generic)

-- | Parameter of Function addRecentSticker
data AddRecentSticker
  = -- | Manually adds a new sticker to the list of recently used stickers. The new sticker is added to the top of the list. If the sticker was already in the list, it is removed from the list first. Only stickers belonging to a sticker set can be added to this list
    AddRecentSticker
      { -- | Pass true to add the sticker to the list of stickers recently attached to photo or video files; pass false to add the sticker to the list of recently sent stickers
        AddRecentSticker -> Bool
is_attached :: Bool,
        -- | Sticker file to add
        AddRecentSticker -> InputFile
sticker :: InputFile
      }
  deriving (Int -> AddRecentSticker -> ShowS
[AddRecentSticker] -> ShowS
AddRecentSticker -> String
(Int -> AddRecentSticker -> ShowS)
-> (AddRecentSticker -> String)
-> ([AddRecentSticker] -> ShowS)
-> Show AddRecentSticker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddRecentSticker] -> ShowS
$cshowList :: [AddRecentSticker] -> ShowS
show :: AddRecentSticker -> String
$cshow :: AddRecentSticker -> String
showsPrec :: Int -> AddRecentSticker -> ShowS
$cshowsPrec :: Int -> AddRecentSticker -> ShowS
Show, AddRecentSticker -> AddRecentSticker -> Bool
(AddRecentSticker -> AddRecentSticker -> Bool)
-> (AddRecentSticker -> AddRecentSticker -> Bool)
-> Eq AddRecentSticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddRecentSticker -> AddRecentSticker -> Bool
$c/= :: AddRecentSticker -> AddRecentSticker -> Bool
== :: AddRecentSticker -> AddRecentSticker -> Bool
$c== :: AddRecentSticker -> AddRecentSticker -> Bool
Eq, (forall x. AddRecentSticker -> Rep AddRecentSticker x)
-> (forall x. Rep AddRecentSticker x -> AddRecentSticker)
-> Generic AddRecentSticker
forall x. Rep AddRecentSticker x -> AddRecentSticker
forall x. AddRecentSticker -> Rep AddRecentSticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddRecentSticker x -> AddRecentSticker
$cfrom :: forall x. AddRecentSticker -> Rep AddRecentSticker x
Generic)

-- | Parameter of Function removeRecentSticker
data RemoveRecentSticker
  = -- | Removes a sticker from the list of recently used stickers
    RemoveRecentSticker
      { -- | Pass true to remove the sticker from the list of stickers recently attached to photo or video files; pass false to remove the sticker from the list of recently sent stickers
        RemoveRecentSticker -> Bool
is_attached :: Bool,
        -- | Sticker file to delete
        RemoveRecentSticker -> InputFile
sticker :: InputFile
      }
  deriving (Int -> RemoveRecentSticker -> ShowS
[RemoveRecentSticker] -> ShowS
RemoveRecentSticker -> String
(Int -> RemoveRecentSticker -> ShowS)
-> (RemoveRecentSticker -> String)
-> ([RemoveRecentSticker] -> ShowS)
-> Show RemoveRecentSticker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRecentSticker] -> ShowS
$cshowList :: [RemoveRecentSticker] -> ShowS
show :: RemoveRecentSticker -> String
$cshow :: RemoveRecentSticker -> String
showsPrec :: Int -> RemoveRecentSticker -> ShowS
$cshowsPrec :: Int -> RemoveRecentSticker -> ShowS
Show, RemoveRecentSticker -> RemoveRecentSticker -> Bool
(RemoveRecentSticker -> RemoveRecentSticker -> Bool)
-> (RemoveRecentSticker -> RemoveRecentSticker -> Bool)
-> Eq RemoveRecentSticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRecentSticker -> RemoveRecentSticker -> Bool
$c/= :: RemoveRecentSticker -> RemoveRecentSticker -> Bool
== :: RemoveRecentSticker -> RemoveRecentSticker -> Bool
$c== :: RemoveRecentSticker -> RemoveRecentSticker -> Bool
Eq, (forall x. RemoveRecentSticker -> Rep RemoveRecentSticker x)
-> (forall x. Rep RemoveRecentSticker x -> RemoveRecentSticker)
-> Generic RemoveRecentSticker
forall x. Rep RemoveRecentSticker x -> RemoveRecentSticker
forall x. RemoveRecentSticker -> Rep RemoveRecentSticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveRecentSticker x -> RemoveRecentSticker
$cfrom :: forall x. RemoveRecentSticker -> Rep RemoveRecentSticker x
Generic)

-- | Parameter of Function clearRecentStickers
data ClearRecentStickers
  = -- | Clears the list of recently used stickers
    ClearRecentStickers
      { -- | Pass true to clear the list of stickers recently attached to photo or video files; pass false to clear the list of recently sent stickers
        ClearRecentStickers -> Bool
is_attached :: Bool
      }
  deriving (Int -> ClearRecentStickers -> ShowS
[ClearRecentStickers] -> ShowS
ClearRecentStickers -> String
(Int -> ClearRecentStickers -> ShowS)
-> (ClearRecentStickers -> String)
-> ([ClearRecentStickers] -> ShowS)
-> Show ClearRecentStickers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ClearRecentStickers] -> ShowS
$cshowList :: [ClearRecentStickers] -> ShowS
show :: ClearRecentStickers -> String
$cshow :: ClearRecentStickers -> String
showsPrec :: Int -> ClearRecentStickers -> ShowS
$cshowsPrec :: Int -> ClearRecentStickers -> ShowS
Show, ClearRecentStickers -> ClearRecentStickers -> Bool
(ClearRecentStickers -> ClearRecentStickers -> Bool)
-> (ClearRecentStickers -> ClearRecentStickers -> Bool)
-> Eq ClearRecentStickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ClearRecentStickers -> ClearRecentStickers -> Bool
$c/= :: ClearRecentStickers -> ClearRecentStickers -> Bool
== :: ClearRecentStickers -> ClearRecentStickers -> Bool
$c== :: ClearRecentStickers -> ClearRecentStickers -> Bool
Eq, (forall x. ClearRecentStickers -> Rep ClearRecentStickers x)
-> (forall x. Rep ClearRecentStickers x -> ClearRecentStickers)
-> Generic ClearRecentStickers
forall x. Rep ClearRecentStickers x -> ClearRecentStickers
forall x. ClearRecentStickers -> Rep ClearRecentStickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ClearRecentStickers x -> ClearRecentStickers
$cfrom :: forall x. ClearRecentStickers -> Rep ClearRecentStickers x
Generic)

-- | Parameter of Function getFavoriteStickers
data GetFavoriteStickers
  = -- | Returns favorite stickers
    GetFavoriteStickers
      {
      }
  deriving (Int -> GetFavoriteStickers -> ShowS
[GetFavoriteStickers] -> ShowS
GetFavoriteStickers -> String
(Int -> GetFavoriteStickers -> ShowS)
-> (GetFavoriteStickers -> String)
-> ([GetFavoriteStickers] -> ShowS)
-> Show GetFavoriteStickers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetFavoriteStickers] -> ShowS
$cshowList :: [GetFavoriteStickers] -> ShowS
show :: GetFavoriteStickers -> String
$cshow :: GetFavoriteStickers -> String
showsPrec :: Int -> GetFavoriteStickers -> ShowS
$cshowsPrec :: Int -> GetFavoriteStickers -> ShowS
Show, GetFavoriteStickers -> GetFavoriteStickers -> Bool
(GetFavoriteStickers -> GetFavoriteStickers -> Bool)
-> (GetFavoriteStickers -> GetFavoriteStickers -> Bool)
-> Eq GetFavoriteStickers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetFavoriteStickers -> GetFavoriteStickers -> Bool
$c/= :: GetFavoriteStickers -> GetFavoriteStickers -> Bool
== :: GetFavoriteStickers -> GetFavoriteStickers -> Bool
$c== :: GetFavoriteStickers -> GetFavoriteStickers -> Bool
Eq, (forall x. GetFavoriteStickers -> Rep GetFavoriteStickers x)
-> (forall x. Rep GetFavoriteStickers x -> GetFavoriteStickers)
-> Generic GetFavoriteStickers
forall x. Rep GetFavoriteStickers x -> GetFavoriteStickers
forall x. GetFavoriteStickers -> Rep GetFavoriteStickers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetFavoriteStickers x -> GetFavoriteStickers
$cfrom :: forall x. GetFavoriteStickers -> Rep GetFavoriteStickers x
Generic)

-- | Parameter of Function addFavoriteSticker
data AddFavoriteSticker
  = -- | Adds a new sticker to the list of favorite stickers. The new sticker is added to the top of the list. If the sticker was already in the list, it is removed from the list first. Only stickers belonging to a sticker set can be added to this list
    AddFavoriteSticker
      { -- | Sticker file to add
        AddFavoriteSticker -> InputFile
sticker :: InputFile
      }
  deriving (Int -> AddFavoriteSticker -> ShowS
[AddFavoriteSticker] -> ShowS
AddFavoriteSticker -> String
(Int -> AddFavoriteSticker -> ShowS)
-> (AddFavoriteSticker -> String)
-> ([AddFavoriteSticker] -> ShowS)
-> Show AddFavoriteSticker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddFavoriteSticker] -> ShowS
$cshowList :: [AddFavoriteSticker] -> ShowS
show :: AddFavoriteSticker -> String
$cshow :: AddFavoriteSticker -> String
showsPrec :: Int -> AddFavoriteSticker -> ShowS
$cshowsPrec :: Int -> AddFavoriteSticker -> ShowS
Show, AddFavoriteSticker -> AddFavoriteSticker -> Bool
(AddFavoriteSticker -> AddFavoriteSticker -> Bool)
-> (AddFavoriteSticker -> AddFavoriteSticker -> Bool)
-> Eq AddFavoriteSticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddFavoriteSticker -> AddFavoriteSticker -> Bool
$c/= :: AddFavoriteSticker -> AddFavoriteSticker -> Bool
== :: AddFavoriteSticker -> AddFavoriteSticker -> Bool
$c== :: AddFavoriteSticker -> AddFavoriteSticker -> Bool
Eq, (forall x. AddFavoriteSticker -> Rep AddFavoriteSticker x)
-> (forall x. Rep AddFavoriteSticker x -> AddFavoriteSticker)
-> Generic AddFavoriteSticker
forall x. Rep AddFavoriteSticker x -> AddFavoriteSticker
forall x. AddFavoriteSticker -> Rep AddFavoriteSticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddFavoriteSticker x -> AddFavoriteSticker
$cfrom :: forall x. AddFavoriteSticker -> Rep AddFavoriteSticker x
Generic)

-- | Parameter of Function removeFavoriteSticker
data RemoveFavoriteSticker
  = -- | Removes a sticker from the list of favorite stickers
    RemoveFavoriteSticker
      { -- | Sticker file to delete from the list
        RemoveFavoriteSticker -> InputFile
sticker :: InputFile
      }
  deriving (Int -> RemoveFavoriteSticker -> ShowS
[RemoveFavoriteSticker] -> ShowS
RemoveFavoriteSticker -> String
(Int -> RemoveFavoriteSticker -> ShowS)
-> (RemoveFavoriteSticker -> String)
-> ([RemoveFavoriteSticker] -> ShowS)
-> Show RemoveFavoriteSticker
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveFavoriteSticker] -> ShowS
$cshowList :: [RemoveFavoriteSticker] -> ShowS
show :: RemoveFavoriteSticker -> String
$cshow :: RemoveFavoriteSticker -> String
showsPrec :: Int -> RemoveFavoriteSticker -> ShowS
$cshowsPrec :: Int -> RemoveFavoriteSticker -> ShowS
Show, RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool
(RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool)
-> (RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool)
-> Eq RemoveFavoriteSticker
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool
$c/= :: RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool
== :: RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool
$c== :: RemoveFavoriteSticker -> RemoveFavoriteSticker -> Bool
Eq, (forall x. RemoveFavoriteSticker -> Rep RemoveFavoriteSticker x)
-> (forall x. Rep RemoveFavoriteSticker x -> RemoveFavoriteSticker)
-> Generic RemoveFavoriteSticker
forall x. Rep RemoveFavoriteSticker x -> RemoveFavoriteSticker
forall x. RemoveFavoriteSticker -> Rep RemoveFavoriteSticker x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveFavoriteSticker x -> RemoveFavoriteSticker
$cfrom :: forall x. RemoveFavoriteSticker -> Rep RemoveFavoriteSticker x
Generic)

-- | Parameter of Function getStickerEmojis
data GetStickerEmojis
  = -- | Returns emoji corresponding to a sticker. The list is only for informational purposes, because a sticker is always sent with a fixed emoji from the corresponding Sticker object
    GetStickerEmojis
      { -- | Sticker file identifier
        GetStickerEmojis -> InputFile
sticker :: InputFile
      }
  deriving (Int -> GetStickerEmojis -> ShowS
[GetStickerEmojis] -> ShowS
GetStickerEmojis -> String
(Int -> GetStickerEmojis -> ShowS)
-> (GetStickerEmojis -> String)
-> ([GetStickerEmojis] -> ShowS)
-> Show GetStickerEmojis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStickerEmojis] -> ShowS
$cshowList :: [GetStickerEmojis] -> ShowS
show :: GetStickerEmojis -> String
$cshow :: GetStickerEmojis -> String
showsPrec :: Int -> GetStickerEmojis -> ShowS
$cshowsPrec :: Int -> GetStickerEmojis -> ShowS
Show, GetStickerEmojis -> GetStickerEmojis -> Bool
(GetStickerEmojis -> GetStickerEmojis -> Bool)
-> (GetStickerEmojis -> GetStickerEmojis -> Bool)
-> Eq GetStickerEmojis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStickerEmojis -> GetStickerEmojis -> Bool
$c/= :: GetStickerEmojis -> GetStickerEmojis -> Bool
== :: GetStickerEmojis -> GetStickerEmojis -> Bool
$c== :: GetStickerEmojis -> GetStickerEmojis -> Bool
Eq, (forall x. GetStickerEmojis -> Rep GetStickerEmojis x)
-> (forall x. Rep GetStickerEmojis x -> GetStickerEmojis)
-> Generic GetStickerEmojis
forall x. Rep GetStickerEmojis x -> GetStickerEmojis
forall x. GetStickerEmojis -> Rep GetStickerEmojis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetStickerEmojis x -> GetStickerEmojis
$cfrom :: forall x. GetStickerEmojis -> Rep GetStickerEmojis x
Generic)

-- | Parameter of Function searchEmojis
data SearchEmojis
  = -- | Searches for emojis by keywords. Supported only if the file database is enabled
    SearchEmojis
      { -- | Text to search for
        SearchEmojis -> T
text :: T,
        -- | True, if only emojis, which exactly match text needs to be returned
        SearchEmojis -> Bool
exact_match :: Bool,
        -- | List of possible IETF language tags of the user's input language; may be empty if unknown
        SearchEmojis -> [T]
input_language_codes :: ([]) (T)
      }
  deriving (Int -> SearchEmojis -> ShowS
[SearchEmojis] -> ShowS
SearchEmojis -> String
(Int -> SearchEmojis -> ShowS)
-> (SearchEmojis -> String)
-> ([SearchEmojis] -> ShowS)
-> Show SearchEmojis
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchEmojis] -> ShowS
$cshowList :: [SearchEmojis] -> ShowS
show :: SearchEmojis -> String
$cshow :: SearchEmojis -> String
showsPrec :: Int -> SearchEmojis -> ShowS
$cshowsPrec :: Int -> SearchEmojis -> ShowS
Show, SearchEmojis -> SearchEmojis -> Bool
(SearchEmojis -> SearchEmojis -> Bool)
-> (SearchEmojis -> SearchEmojis -> Bool) -> Eq SearchEmojis
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchEmojis -> SearchEmojis -> Bool
$c/= :: SearchEmojis -> SearchEmojis -> Bool
== :: SearchEmojis -> SearchEmojis -> Bool
$c== :: SearchEmojis -> SearchEmojis -> Bool
Eq, (forall x. SearchEmojis -> Rep SearchEmojis x)
-> (forall x. Rep SearchEmojis x -> SearchEmojis)
-> Generic SearchEmojis
forall x. Rep SearchEmojis x -> SearchEmojis
forall x. SearchEmojis -> Rep SearchEmojis x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchEmojis x -> SearchEmojis
$cfrom :: forall x. SearchEmojis -> Rep SearchEmojis x
Generic)

-- | Parameter of Function getEmojiSuggestionsUrl
data GetEmojiSuggestionsUrl
  = -- | Returns an HTTP URL which can be used to automatically log in to the translation platform and suggest new emoji replacements. The URL will be valid for 30 seconds after generation
    GetEmojiSuggestionsUrl
      { -- | Language code for which the emoji replacements will be suggested
        GetEmojiSuggestionsUrl -> T
language_code :: T
      }
  deriving (Int -> GetEmojiSuggestionsUrl -> ShowS
[GetEmojiSuggestionsUrl] -> ShowS
GetEmojiSuggestionsUrl -> String
(Int -> GetEmojiSuggestionsUrl -> ShowS)
-> (GetEmojiSuggestionsUrl -> String)
-> ([GetEmojiSuggestionsUrl] -> ShowS)
-> Show GetEmojiSuggestionsUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetEmojiSuggestionsUrl] -> ShowS
$cshowList :: [GetEmojiSuggestionsUrl] -> ShowS
show :: GetEmojiSuggestionsUrl -> String
$cshow :: GetEmojiSuggestionsUrl -> String
showsPrec :: Int -> GetEmojiSuggestionsUrl -> ShowS
$cshowsPrec :: Int -> GetEmojiSuggestionsUrl -> ShowS
Show, GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool
(GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool)
-> (GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool)
-> Eq GetEmojiSuggestionsUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool
$c/= :: GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool
== :: GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool
$c== :: GetEmojiSuggestionsUrl -> GetEmojiSuggestionsUrl -> Bool
Eq, (forall x. GetEmojiSuggestionsUrl -> Rep GetEmojiSuggestionsUrl x)
-> (forall x.
    Rep GetEmojiSuggestionsUrl x -> GetEmojiSuggestionsUrl)
-> Generic GetEmojiSuggestionsUrl
forall x. Rep GetEmojiSuggestionsUrl x -> GetEmojiSuggestionsUrl
forall x. GetEmojiSuggestionsUrl -> Rep GetEmojiSuggestionsUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetEmojiSuggestionsUrl x -> GetEmojiSuggestionsUrl
$cfrom :: forall x. GetEmojiSuggestionsUrl -> Rep GetEmojiSuggestionsUrl x
Generic)

-- | Parameter of Function getSavedAnimations
data GetSavedAnimations
  = -- | Returns saved animations
    GetSavedAnimations
      {
      }
  deriving (Int -> GetSavedAnimations -> ShowS
[GetSavedAnimations] -> ShowS
GetSavedAnimations -> String
(Int -> GetSavedAnimations -> ShowS)
-> (GetSavedAnimations -> String)
-> ([GetSavedAnimations] -> ShowS)
-> Show GetSavedAnimations
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSavedAnimations] -> ShowS
$cshowList :: [GetSavedAnimations] -> ShowS
show :: GetSavedAnimations -> String
$cshow :: GetSavedAnimations -> String
showsPrec :: Int -> GetSavedAnimations -> ShowS
$cshowsPrec :: Int -> GetSavedAnimations -> ShowS
Show, GetSavedAnimations -> GetSavedAnimations -> Bool
(GetSavedAnimations -> GetSavedAnimations -> Bool)
-> (GetSavedAnimations -> GetSavedAnimations -> Bool)
-> Eq GetSavedAnimations
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSavedAnimations -> GetSavedAnimations -> Bool
$c/= :: GetSavedAnimations -> GetSavedAnimations -> Bool
== :: GetSavedAnimations -> GetSavedAnimations -> Bool
$c== :: GetSavedAnimations -> GetSavedAnimations -> Bool
Eq, (forall x. GetSavedAnimations -> Rep GetSavedAnimations x)
-> (forall x. Rep GetSavedAnimations x -> GetSavedAnimations)
-> Generic GetSavedAnimations
forall x. Rep GetSavedAnimations x -> GetSavedAnimations
forall x. GetSavedAnimations -> Rep GetSavedAnimations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSavedAnimations x -> GetSavedAnimations
$cfrom :: forall x. GetSavedAnimations -> Rep GetSavedAnimations x
Generic)

-- | Parameter of Function addSavedAnimation
data AddSavedAnimation
  = -- | Manually adds a new animation to the list of saved animations. The new animation is added to the beginning of the list. If the animation was already in the list, it is removed first. Only non-secret video animations with MIME type "video/mp4" can be added to the list
    AddSavedAnimation
      { -- | The animation file to be added. Only animations known to the server (i.e. successfully sent via a message) can be added to the list
        AddSavedAnimation -> InputFile
animation :: InputFile
      }
  deriving (Int -> AddSavedAnimation -> ShowS
[AddSavedAnimation] -> ShowS
AddSavedAnimation -> String
(Int -> AddSavedAnimation -> ShowS)
-> (AddSavedAnimation -> String)
-> ([AddSavedAnimation] -> ShowS)
-> Show AddSavedAnimation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddSavedAnimation] -> ShowS
$cshowList :: [AddSavedAnimation] -> ShowS
show :: AddSavedAnimation -> String
$cshow :: AddSavedAnimation -> String
showsPrec :: Int -> AddSavedAnimation -> ShowS
$cshowsPrec :: Int -> AddSavedAnimation -> ShowS
Show, AddSavedAnimation -> AddSavedAnimation -> Bool
(AddSavedAnimation -> AddSavedAnimation -> Bool)
-> (AddSavedAnimation -> AddSavedAnimation -> Bool)
-> Eq AddSavedAnimation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddSavedAnimation -> AddSavedAnimation -> Bool
$c/= :: AddSavedAnimation -> AddSavedAnimation -> Bool
== :: AddSavedAnimation -> AddSavedAnimation -> Bool
$c== :: AddSavedAnimation -> AddSavedAnimation -> Bool
Eq, (forall x. AddSavedAnimation -> Rep AddSavedAnimation x)
-> (forall x. Rep AddSavedAnimation x -> AddSavedAnimation)
-> Generic AddSavedAnimation
forall x. Rep AddSavedAnimation x -> AddSavedAnimation
forall x. AddSavedAnimation -> Rep AddSavedAnimation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddSavedAnimation x -> AddSavedAnimation
$cfrom :: forall x. AddSavedAnimation -> Rep AddSavedAnimation x
Generic)

-- | Parameter of Function removeSavedAnimation
data RemoveSavedAnimation
  = -- | Removes an animation from the list of saved animations
    RemoveSavedAnimation
      { -- | Animation file to be removed
        RemoveSavedAnimation -> InputFile
animation :: InputFile
      }
  deriving (Int -> RemoveSavedAnimation -> ShowS
[RemoveSavedAnimation] -> ShowS
RemoveSavedAnimation -> String
(Int -> RemoveSavedAnimation -> ShowS)
-> (RemoveSavedAnimation -> String)
-> ([RemoveSavedAnimation] -> ShowS)
-> Show RemoveSavedAnimation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveSavedAnimation] -> ShowS
$cshowList :: [RemoveSavedAnimation] -> ShowS
show :: RemoveSavedAnimation -> String
$cshow :: RemoveSavedAnimation -> String
showsPrec :: Int -> RemoveSavedAnimation -> ShowS
$cshowsPrec :: Int -> RemoveSavedAnimation -> ShowS
Show, RemoveSavedAnimation -> RemoveSavedAnimation -> Bool
(RemoveSavedAnimation -> RemoveSavedAnimation -> Bool)
-> (RemoveSavedAnimation -> RemoveSavedAnimation -> Bool)
-> Eq RemoveSavedAnimation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveSavedAnimation -> RemoveSavedAnimation -> Bool
$c/= :: RemoveSavedAnimation -> RemoveSavedAnimation -> Bool
== :: RemoveSavedAnimation -> RemoveSavedAnimation -> Bool
$c== :: RemoveSavedAnimation -> RemoveSavedAnimation -> Bool
Eq, (forall x. RemoveSavedAnimation -> Rep RemoveSavedAnimation x)
-> (forall x. Rep RemoveSavedAnimation x -> RemoveSavedAnimation)
-> Generic RemoveSavedAnimation
forall x. Rep RemoveSavedAnimation x -> RemoveSavedAnimation
forall x. RemoveSavedAnimation -> Rep RemoveSavedAnimation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveSavedAnimation x -> RemoveSavedAnimation
$cfrom :: forall x. RemoveSavedAnimation -> Rep RemoveSavedAnimation x
Generic)

-- | Parameter of Function getRecentInlineBots
data GetRecentInlineBots
  = -- | Returns up to 20 recently used inline bots in the order of their last usage
    GetRecentInlineBots
      {
      }
  deriving (Int -> GetRecentInlineBots -> ShowS
[GetRecentInlineBots] -> ShowS
GetRecentInlineBots -> String
(Int -> GetRecentInlineBots -> ShowS)
-> (GetRecentInlineBots -> String)
-> ([GetRecentInlineBots] -> ShowS)
-> Show GetRecentInlineBots
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecentInlineBots] -> ShowS
$cshowList :: [GetRecentInlineBots] -> ShowS
show :: GetRecentInlineBots -> String
$cshow :: GetRecentInlineBots -> String
showsPrec :: Int -> GetRecentInlineBots -> ShowS
$cshowsPrec :: Int -> GetRecentInlineBots -> ShowS
Show, GetRecentInlineBots -> GetRecentInlineBots -> Bool
(GetRecentInlineBots -> GetRecentInlineBots -> Bool)
-> (GetRecentInlineBots -> GetRecentInlineBots -> Bool)
-> Eq GetRecentInlineBots
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecentInlineBots -> GetRecentInlineBots -> Bool
$c/= :: GetRecentInlineBots -> GetRecentInlineBots -> Bool
== :: GetRecentInlineBots -> GetRecentInlineBots -> Bool
$c== :: GetRecentInlineBots -> GetRecentInlineBots -> Bool
Eq, (forall x. GetRecentInlineBots -> Rep GetRecentInlineBots x)
-> (forall x. Rep GetRecentInlineBots x -> GetRecentInlineBots)
-> Generic GetRecentInlineBots
forall x. Rep GetRecentInlineBots x -> GetRecentInlineBots
forall x. GetRecentInlineBots -> Rep GetRecentInlineBots x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetRecentInlineBots x -> GetRecentInlineBots
$cfrom :: forall x. GetRecentInlineBots -> Rep GetRecentInlineBots x
Generic)

-- | Parameter of Function searchHashtags
data SearchHashtags
  = -- | Searches for recently used hashtags by their prefix
    SearchHashtags
      { -- | Hashtag prefix to search for
        SearchHashtags -> T
prefix :: T,
        -- | The maximum number of hashtags to be returned
        SearchHashtags -> Int
limit :: I32
      }
  deriving (Int -> SearchHashtags -> ShowS
[SearchHashtags] -> ShowS
SearchHashtags -> String
(Int -> SearchHashtags -> ShowS)
-> (SearchHashtags -> String)
-> ([SearchHashtags] -> ShowS)
-> Show SearchHashtags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchHashtags] -> ShowS
$cshowList :: [SearchHashtags] -> ShowS
show :: SearchHashtags -> String
$cshow :: SearchHashtags -> String
showsPrec :: Int -> SearchHashtags -> ShowS
$cshowsPrec :: Int -> SearchHashtags -> ShowS
Show, SearchHashtags -> SearchHashtags -> Bool
(SearchHashtags -> SearchHashtags -> Bool)
-> (SearchHashtags -> SearchHashtags -> Bool) -> Eq SearchHashtags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchHashtags -> SearchHashtags -> Bool
$c/= :: SearchHashtags -> SearchHashtags -> Bool
== :: SearchHashtags -> SearchHashtags -> Bool
$c== :: SearchHashtags -> SearchHashtags -> Bool
Eq, (forall x. SearchHashtags -> Rep SearchHashtags x)
-> (forall x. Rep SearchHashtags x -> SearchHashtags)
-> Generic SearchHashtags
forall x. Rep SearchHashtags x -> SearchHashtags
forall x. SearchHashtags -> Rep SearchHashtags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchHashtags x -> SearchHashtags
$cfrom :: forall x. SearchHashtags -> Rep SearchHashtags x
Generic)

-- | Parameter of Function removeRecentHashtag
data RemoveRecentHashtag
  = -- | Removes a hashtag from the list of recently used hashtags
    RemoveRecentHashtag
      { -- | Hashtag to delete
        RemoveRecentHashtag -> T
hashtag :: T
      }
  deriving (Int -> RemoveRecentHashtag -> ShowS
[RemoveRecentHashtag] -> ShowS
RemoveRecentHashtag -> String
(Int -> RemoveRecentHashtag -> ShowS)
-> (RemoveRecentHashtag -> String)
-> ([RemoveRecentHashtag] -> ShowS)
-> Show RemoveRecentHashtag
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveRecentHashtag] -> ShowS
$cshowList :: [RemoveRecentHashtag] -> ShowS
show :: RemoveRecentHashtag -> String
$cshow :: RemoveRecentHashtag -> String
showsPrec :: Int -> RemoveRecentHashtag -> ShowS
$cshowsPrec :: Int -> RemoveRecentHashtag -> ShowS
Show, RemoveRecentHashtag -> RemoveRecentHashtag -> Bool
(RemoveRecentHashtag -> RemoveRecentHashtag -> Bool)
-> (RemoveRecentHashtag -> RemoveRecentHashtag -> Bool)
-> Eq RemoveRecentHashtag
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveRecentHashtag -> RemoveRecentHashtag -> Bool
$c/= :: RemoveRecentHashtag -> RemoveRecentHashtag -> Bool
== :: RemoveRecentHashtag -> RemoveRecentHashtag -> Bool
$c== :: RemoveRecentHashtag -> RemoveRecentHashtag -> Bool
Eq, (forall x. RemoveRecentHashtag -> Rep RemoveRecentHashtag x)
-> (forall x. Rep RemoveRecentHashtag x -> RemoveRecentHashtag)
-> Generic RemoveRecentHashtag
forall x. Rep RemoveRecentHashtag x -> RemoveRecentHashtag
forall x. RemoveRecentHashtag -> Rep RemoveRecentHashtag x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveRecentHashtag x -> RemoveRecentHashtag
$cfrom :: forall x. RemoveRecentHashtag -> Rep RemoveRecentHashtag x
Generic)

-- | Parameter of Function getWebPagePreview
data GetWebPagePreview
  = -- | Returns a web page preview by the text of the message. Do not call this function too often. Returns a 404 error if the web page has no preview
    GetWebPagePreview
      { -- | Message text with formatting
        GetWebPagePreview -> FormattedText
text :: FormattedText
      }
  deriving (Int -> GetWebPagePreview -> ShowS
[GetWebPagePreview] -> ShowS
GetWebPagePreview -> String
(Int -> GetWebPagePreview -> ShowS)
-> (GetWebPagePreview -> String)
-> ([GetWebPagePreview] -> ShowS)
-> Show GetWebPagePreview
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetWebPagePreview] -> ShowS
$cshowList :: [GetWebPagePreview] -> ShowS
show :: GetWebPagePreview -> String
$cshow :: GetWebPagePreview -> String
showsPrec :: Int -> GetWebPagePreview -> ShowS
$cshowsPrec :: Int -> GetWebPagePreview -> ShowS
Show, GetWebPagePreview -> GetWebPagePreview -> Bool
(GetWebPagePreview -> GetWebPagePreview -> Bool)
-> (GetWebPagePreview -> GetWebPagePreview -> Bool)
-> Eq GetWebPagePreview
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetWebPagePreview -> GetWebPagePreview -> Bool
$c/= :: GetWebPagePreview -> GetWebPagePreview -> Bool
== :: GetWebPagePreview -> GetWebPagePreview -> Bool
$c== :: GetWebPagePreview -> GetWebPagePreview -> Bool
Eq, (forall x. GetWebPagePreview -> Rep GetWebPagePreview x)
-> (forall x. Rep GetWebPagePreview x -> GetWebPagePreview)
-> Generic GetWebPagePreview
forall x. Rep GetWebPagePreview x -> GetWebPagePreview
forall x. GetWebPagePreview -> Rep GetWebPagePreview x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetWebPagePreview x -> GetWebPagePreview
$cfrom :: forall x. GetWebPagePreview -> Rep GetWebPagePreview x
Generic)

-- | Parameter of Function getWebPageInstantView
data GetWebPageInstantView
  = -- | Returns an instant view version of a web page if available. Returns a 404 error if the web page has no instant view page
    GetWebPageInstantView
      { -- | The web page URL
        GetWebPageInstantView -> T
url :: T,
        -- | If true, the full instant view for the web page will be returned
        GetWebPageInstantView -> Bool
force_full :: Bool
      }
  deriving (Int -> GetWebPageInstantView -> ShowS
[GetWebPageInstantView] -> ShowS
GetWebPageInstantView -> String
(Int -> GetWebPageInstantView -> ShowS)
-> (GetWebPageInstantView -> String)
-> ([GetWebPageInstantView] -> ShowS)
-> Show GetWebPageInstantView
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetWebPageInstantView] -> ShowS
$cshowList :: [GetWebPageInstantView] -> ShowS
show :: GetWebPageInstantView -> String
$cshow :: GetWebPageInstantView -> String
showsPrec :: Int -> GetWebPageInstantView -> ShowS
$cshowsPrec :: Int -> GetWebPageInstantView -> ShowS
Show, GetWebPageInstantView -> GetWebPageInstantView -> Bool
(GetWebPageInstantView -> GetWebPageInstantView -> Bool)
-> (GetWebPageInstantView -> GetWebPageInstantView -> Bool)
-> Eq GetWebPageInstantView
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetWebPageInstantView -> GetWebPageInstantView -> Bool
$c/= :: GetWebPageInstantView -> GetWebPageInstantView -> Bool
== :: GetWebPageInstantView -> GetWebPageInstantView -> Bool
$c== :: GetWebPageInstantView -> GetWebPageInstantView -> Bool
Eq, (forall x. GetWebPageInstantView -> Rep GetWebPageInstantView x)
-> (forall x. Rep GetWebPageInstantView x -> GetWebPageInstantView)
-> Generic GetWebPageInstantView
forall x. Rep GetWebPageInstantView x -> GetWebPageInstantView
forall x. GetWebPageInstantView -> Rep GetWebPageInstantView x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetWebPageInstantView x -> GetWebPageInstantView
$cfrom :: forall x. GetWebPageInstantView -> Rep GetWebPageInstantView x
Generic)

-- | Parameter of Function setProfilePhoto
data SetProfilePhoto
  = -- | Uploads a new profile photo for the current user. If something changes, updateUser will be sent
    SetProfilePhoto
      { -- | Profile photo to set. inputFileId and inputFileRemote may still be unsupported
        SetProfilePhoto -> InputFile
photo :: InputFile
      }
  deriving (Int -> SetProfilePhoto -> ShowS
[SetProfilePhoto] -> ShowS
SetProfilePhoto -> String
(Int -> SetProfilePhoto -> ShowS)
-> (SetProfilePhoto -> String)
-> ([SetProfilePhoto] -> ShowS)
-> Show SetProfilePhoto
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetProfilePhoto] -> ShowS
$cshowList :: [SetProfilePhoto] -> ShowS
show :: SetProfilePhoto -> String
$cshow :: SetProfilePhoto -> String
showsPrec :: Int -> SetProfilePhoto -> ShowS
$cshowsPrec :: Int -> SetProfilePhoto -> ShowS
Show, SetProfilePhoto -> SetProfilePhoto -> Bool
(SetProfilePhoto -> SetProfilePhoto -> Bool)
-> (SetProfilePhoto -> SetProfilePhoto -> Bool)
-> Eq SetProfilePhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetProfilePhoto -> SetProfilePhoto -> Bool
$c/= :: SetProfilePhoto -> SetProfilePhoto -> Bool
== :: SetProfilePhoto -> SetProfilePhoto -> Bool
$c== :: SetProfilePhoto -> SetProfilePhoto -> Bool
Eq, (forall x. SetProfilePhoto -> Rep SetProfilePhoto x)
-> (forall x. Rep SetProfilePhoto x -> SetProfilePhoto)
-> Generic SetProfilePhoto
forall x. Rep SetProfilePhoto x -> SetProfilePhoto
forall x. SetProfilePhoto -> Rep SetProfilePhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetProfilePhoto x -> SetProfilePhoto
$cfrom :: forall x. SetProfilePhoto -> Rep SetProfilePhoto x
Generic)

-- | Parameter of Function deleteProfilePhoto
data DeleteProfilePhoto
  = -- | Deletes a profile photo. If something changes, updateUser will be sent
    DeleteProfilePhoto
      { -- | Identifier of the profile photo to delete
        DeleteProfilePhoto -> I64
profile_photo_id :: I64
      }
  deriving (Int -> DeleteProfilePhoto -> ShowS
[DeleteProfilePhoto] -> ShowS
DeleteProfilePhoto -> String
(Int -> DeleteProfilePhoto -> ShowS)
-> (DeleteProfilePhoto -> String)
-> ([DeleteProfilePhoto] -> ShowS)
-> Show DeleteProfilePhoto
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteProfilePhoto] -> ShowS
$cshowList :: [DeleteProfilePhoto] -> ShowS
show :: DeleteProfilePhoto -> String
$cshow :: DeleteProfilePhoto -> String
showsPrec :: Int -> DeleteProfilePhoto -> ShowS
$cshowsPrec :: Int -> DeleteProfilePhoto -> ShowS
Show, DeleteProfilePhoto -> DeleteProfilePhoto -> Bool
(DeleteProfilePhoto -> DeleteProfilePhoto -> Bool)
-> (DeleteProfilePhoto -> DeleteProfilePhoto -> Bool)
-> Eq DeleteProfilePhoto
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteProfilePhoto -> DeleteProfilePhoto -> Bool
$c/= :: DeleteProfilePhoto -> DeleteProfilePhoto -> Bool
== :: DeleteProfilePhoto -> DeleteProfilePhoto -> Bool
$c== :: DeleteProfilePhoto -> DeleteProfilePhoto -> Bool
Eq, (forall x. DeleteProfilePhoto -> Rep DeleteProfilePhoto x)
-> (forall x. Rep DeleteProfilePhoto x -> DeleteProfilePhoto)
-> Generic DeleteProfilePhoto
forall x. Rep DeleteProfilePhoto x -> DeleteProfilePhoto
forall x. DeleteProfilePhoto -> Rep DeleteProfilePhoto x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteProfilePhoto x -> DeleteProfilePhoto
$cfrom :: forall x. DeleteProfilePhoto -> Rep DeleteProfilePhoto x
Generic)

-- | Parameter of Function setName
data SetName
  = -- | Changes the first and last name of the current user. If something changes, updateUser will be sent
    SetName
      { -- | The new value of the first name for the user; 1-64 characters
        SetName -> T
first_name :: T,
        -- | The new value of the optional last name for the user; 0-64 characters
        SetName -> T
last_name :: T
      }
  deriving (Int -> SetName -> ShowS
[SetName] -> ShowS
SetName -> String
(Int -> SetName -> ShowS)
-> (SetName -> String) -> ([SetName] -> ShowS) -> Show SetName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetName] -> ShowS
$cshowList :: [SetName] -> ShowS
show :: SetName -> String
$cshow :: SetName -> String
showsPrec :: Int -> SetName -> ShowS
$cshowsPrec :: Int -> SetName -> ShowS
Show, SetName -> SetName -> Bool
(SetName -> SetName -> Bool)
-> (SetName -> SetName -> Bool) -> Eq SetName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetName -> SetName -> Bool
$c/= :: SetName -> SetName -> Bool
== :: SetName -> SetName -> Bool
$c== :: SetName -> SetName -> Bool
Eq, (forall x. SetName -> Rep SetName x)
-> (forall x. Rep SetName x -> SetName) -> Generic SetName
forall x. Rep SetName x -> SetName
forall x. SetName -> Rep SetName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetName x -> SetName
$cfrom :: forall x. SetName -> Rep SetName x
Generic)

-- | Parameter of Function setBio
data SetBio
  = -- | Changes the bio of the current user
    SetBio
      { -- | The new value of the user bio; 0-70 characters without line feeds
        SetBio -> T
bio :: T
      }
  deriving (Int -> SetBio -> ShowS
[SetBio] -> ShowS
SetBio -> String
(Int -> SetBio -> ShowS)
-> (SetBio -> String) -> ([SetBio] -> ShowS) -> Show SetBio
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetBio] -> ShowS
$cshowList :: [SetBio] -> ShowS
show :: SetBio -> String
$cshow :: SetBio -> String
showsPrec :: Int -> SetBio -> ShowS
$cshowsPrec :: Int -> SetBio -> ShowS
Show, SetBio -> SetBio -> Bool
(SetBio -> SetBio -> Bool)
-> (SetBio -> SetBio -> Bool) -> Eq SetBio
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetBio -> SetBio -> Bool
$c/= :: SetBio -> SetBio -> Bool
== :: SetBio -> SetBio -> Bool
$c== :: SetBio -> SetBio -> Bool
Eq, (forall x. SetBio -> Rep SetBio x)
-> (forall x. Rep SetBio x -> SetBio) -> Generic SetBio
forall x. Rep SetBio x -> SetBio
forall x. SetBio -> Rep SetBio x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetBio x -> SetBio
$cfrom :: forall x. SetBio -> Rep SetBio x
Generic)

-- | Parameter of Function setUsername
data SetUsername
  = -- | Changes the username of the current user. If something changes, updateUser will be sent
    SetUsername
      { -- | The new value of the username. Use an empty string to remove the username
        SetUsername -> T
username :: T
      }
  deriving (Int -> SetUsername -> ShowS
[SetUsername] -> ShowS
SetUsername -> String
(Int -> SetUsername -> ShowS)
-> (SetUsername -> String)
-> ([SetUsername] -> ShowS)
-> Show SetUsername
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetUsername] -> ShowS
$cshowList :: [SetUsername] -> ShowS
show :: SetUsername -> String
$cshow :: SetUsername -> String
showsPrec :: Int -> SetUsername -> ShowS
$cshowsPrec :: Int -> SetUsername -> ShowS
Show, SetUsername -> SetUsername -> Bool
(SetUsername -> SetUsername -> Bool)
-> (SetUsername -> SetUsername -> Bool) -> Eq SetUsername
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetUsername -> SetUsername -> Bool
$c/= :: SetUsername -> SetUsername -> Bool
== :: SetUsername -> SetUsername -> Bool
$c== :: SetUsername -> SetUsername -> Bool
Eq, (forall x. SetUsername -> Rep SetUsername x)
-> (forall x. Rep SetUsername x -> SetUsername)
-> Generic SetUsername
forall x. Rep SetUsername x -> SetUsername
forall x. SetUsername -> Rep SetUsername x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetUsername x -> SetUsername
$cfrom :: forall x. SetUsername -> Rep SetUsername x
Generic)

-- | Parameter of Function setLocation
data SetLocation
  = -- | Changes the location of the current user. Needs to be called if GetOption("is_location_visible") is true and location changes for more than 1 kilometer
    SetLocation
      { -- | The new location of the user
        SetLocation -> Location
location :: Location
      }
  deriving (Int -> SetLocation -> ShowS
[SetLocation] -> ShowS
SetLocation -> String
(Int -> SetLocation -> ShowS)
-> (SetLocation -> String)
-> ([SetLocation] -> ShowS)
-> Show SetLocation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetLocation] -> ShowS
$cshowList :: [SetLocation] -> ShowS
show :: SetLocation -> String
$cshow :: SetLocation -> String
showsPrec :: Int -> SetLocation -> ShowS
$cshowsPrec :: Int -> SetLocation -> ShowS
Show, SetLocation -> SetLocation -> Bool
(SetLocation -> SetLocation -> Bool)
-> (SetLocation -> SetLocation -> Bool) -> Eq SetLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLocation -> SetLocation -> Bool
$c/= :: SetLocation -> SetLocation -> Bool
== :: SetLocation -> SetLocation -> Bool
$c== :: SetLocation -> SetLocation -> Bool
Eq, (forall x. SetLocation -> Rep SetLocation x)
-> (forall x. Rep SetLocation x -> SetLocation)
-> Generic SetLocation
forall x. Rep SetLocation x -> SetLocation
forall x. SetLocation -> Rep SetLocation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetLocation x -> SetLocation
$cfrom :: forall x. SetLocation -> Rep SetLocation x
Generic)

-- | Parameter of Function changePhoneNumber
data ChangePhoneNumber
  = -- | Changes the phone number of the user and sends an authentication code to the user's new phone number. On success, returns information about the sent code
    ChangePhoneNumber
      { -- | The new phone number of the user in international format
        ChangePhoneNumber -> T
phone_number :: T,
        -- | Settings for the authentication of the user's phone number
        ChangePhoneNumber -> PhoneNumberAuthenticationSettings
settings :: PhoneNumberAuthenticationSettings
      }
  deriving (Int -> ChangePhoneNumber -> ShowS
[ChangePhoneNumber] -> ShowS
ChangePhoneNumber -> String
(Int -> ChangePhoneNumber -> ShowS)
-> (ChangePhoneNumber -> String)
-> ([ChangePhoneNumber] -> ShowS)
-> Show ChangePhoneNumber
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ChangePhoneNumber] -> ShowS
$cshowList :: [ChangePhoneNumber] -> ShowS
show :: ChangePhoneNumber -> String
$cshow :: ChangePhoneNumber -> String
showsPrec :: Int -> ChangePhoneNumber -> ShowS
$cshowsPrec :: Int -> ChangePhoneNumber -> ShowS
Show, ChangePhoneNumber -> ChangePhoneNumber -> Bool
(ChangePhoneNumber -> ChangePhoneNumber -> Bool)
-> (ChangePhoneNumber -> ChangePhoneNumber -> Bool)
-> Eq ChangePhoneNumber
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ChangePhoneNumber -> ChangePhoneNumber -> Bool
$c/= :: ChangePhoneNumber -> ChangePhoneNumber -> Bool
== :: ChangePhoneNumber -> ChangePhoneNumber -> Bool
$c== :: ChangePhoneNumber -> ChangePhoneNumber -> Bool
Eq, (forall x. ChangePhoneNumber -> Rep ChangePhoneNumber x)
-> (forall x. Rep ChangePhoneNumber x -> ChangePhoneNumber)
-> Generic ChangePhoneNumber
forall x. Rep ChangePhoneNumber x -> ChangePhoneNumber
forall x. ChangePhoneNumber -> Rep ChangePhoneNumber x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ChangePhoneNumber x -> ChangePhoneNumber
$cfrom :: forall x. ChangePhoneNumber -> Rep ChangePhoneNumber x
Generic)

-- | Parameter of Function resendChangePhoneNumberCode
data ResendChangePhoneNumberCode
  = -- | Re-sends the authentication code sent to confirm a new phone number for the user. Works only if the previously received authenticationCodeInfo next_code_type was not null
    ResendChangePhoneNumberCode
      {
      }
  deriving (Int -> ResendChangePhoneNumberCode -> ShowS
[ResendChangePhoneNumberCode] -> ShowS
ResendChangePhoneNumberCode -> String
(Int -> ResendChangePhoneNumberCode -> ShowS)
-> (ResendChangePhoneNumberCode -> String)
-> ([ResendChangePhoneNumberCode] -> ShowS)
-> Show ResendChangePhoneNumberCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendChangePhoneNumberCode] -> ShowS
$cshowList :: [ResendChangePhoneNumberCode] -> ShowS
show :: ResendChangePhoneNumberCode -> String
$cshow :: ResendChangePhoneNumberCode -> String
showsPrec :: Int -> ResendChangePhoneNumberCode -> ShowS
$cshowsPrec :: Int -> ResendChangePhoneNumberCode -> ShowS
Show, ResendChangePhoneNumberCode -> ResendChangePhoneNumberCode -> Bool
(ResendChangePhoneNumberCode
 -> ResendChangePhoneNumberCode -> Bool)
-> (ResendChangePhoneNumberCode
    -> ResendChangePhoneNumberCode -> Bool)
-> Eq ResendChangePhoneNumberCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendChangePhoneNumberCode -> ResendChangePhoneNumberCode -> Bool
$c/= :: ResendChangePhoneNumberCode -> ResendChangePhoneNumberCode -> Bool
== :: ResendChangePhoneNumberCode -> ResendChangePhoneNumberCode -> Bool
$c== :: ResendChangePhoneNumberCode -> ResendChangePhoneNumberCode -> Bool
Eq, (forall x.
 ResendChangePhoneNumberCode -> Rep ResendChangePhoneNumberCode x)
-> (forall x.
    Rep ResendChangePhoneNumberCode x -> ResendChangePhoneNumberCode)
-> Generic ResendChangePhoneNumberCode
forall x.
Rep ResendChangePhoneNumberCode x -> ResendChangePhoneNumberCode
forall x.
ResendChangePhoneNumberCode -> Rep ResendChangePhoneNumberCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendChangePhoneNumberCode x -> ResendChangePhoneNumberCode
$cfrom :: forall x.
ResendChangePhoneNumberCode -> Rep ResendChangePhoneNumberCode x
Generic)

-- | Parameter of Function checkChangePhoneNumberCode
data CheckChangePhoneNumberCode
  = -- | Checks the authentication code sent to confirm a new phone number of the user
    CheckChangePhoneNumberCode
      { -- | Verification code received by SMS, phone call or flash call
        CheckChangePhoneNumberCode -> T
code :: T
      }
  deriving (Int -> CheckChangePhoneNumberCode -> ShowS
[CheckChangePhoneNumberCode] -> ShowS
CheckChangePhoneNumberCode -> String
(Int -> CheckChangePhoneNumberCode -> ShowS)
-> (CheckChangePhoneNumberCode -> String)
-> ([CheckChangePhoneNumberCode] -> ShowS)
-> Show CheckChangePhoneNumberCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckChangePhoneNumberCode] -> ShowS
$cshowList :: [CheckChangePhoneNumberCode] -> ShowS
show :: CheckChangePhoneNumberCode -> String
$cshow :: CheckChangePhoneNumberCode -> String
showsPrec :: Int -> CheckChangePhoneNumberCode -> ShowS
$cshowsPrec :: Int -> CheckChangePhoneNumberCode -> ShowS
Show, CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool
(CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool)
-> (CheckChangePhoneNumberCode
    -> CheckChangePhoneNumberCode -> Bool)
-> Eq CheckChangePhoneNumberCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool
$c/= :: CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool
== :: CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool
$c== :: CheckChangePhoneNumberCode -> CheckChangePhoneNumberCode -> Bool
Eq, (forall x.
 CheckChangePhoneNumberCode -> Rep CheckChangePhoneNumberCode x)
-> (forall x.
    Rep CheckChangePhoneNumberCode x -> CheckChangePhoneNumberCode)
-> Generic CheckChangePhoneNumberCode
forall x.
Rep CheckChangePhoneNumberCode x -> CheckChangePhoneNumberCode
forall x.
CheckChangePhoneNumberCode -> Rep CheckChangePhoneNumberCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckChangePhoneNumberCode x -> CheckChangePhoneNumberCode
$cfrom :: forall x.
CheckChangePhoneNumberCode -> Rep CheckChangePhoneNumberCode x
Generic)

-- | Parameter of Function setCommands
data SetCommands
  = -- | Sets the list of commands supported by the bot; for bots only
    SetCommands
      { -- | List of the bot's commands
        SetCommands -> [BotCommand]
commands :: ([]) (BotCommand)
      }
  deriving (Int -> SetCommands -> ShowS
[SetCommands] -> ShowS
SetCommands -> String
(Int -> SetCommands -> ShowS)
-> (SetCommands -> String)
-> ([SetCommands] -> ShowS)
-> Show SetCommands
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetCommands] -> ShowS
$cshowList :: [SetCommands] -> ShowS
show :: SetCommands -> String
$cshow :: SetCommands -> String
showsPrec :: Int -> SetCommands -> ShowS
$cshowsPrec :: Int -> SetCommands -> ShowS
Show, SetCommands -> SetCommands -> Bool
(SetCommands -> SetCommands -> Bool)
-> (SetCommands -> SetCommands -> Bool) -> Eq SetCommands
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetCommands -> SetCommands -> Bool
$c/= :: SetCommands -> SetCommands -> Bool
== :: SetCommands -> SetCommands -> Bool
$c== :: SetCommands -> SetCommands -> Bool
Eq, (forall x. SetCommands -> Rep SetCommands x)
-> (forall x. Rep SetCommands x -> SetCommands)
-> Generic SetCommands
forall x. Rep SetCommands x -> SetCommands
forall x. SetCommands -> Rep SetCommands x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetCommands x -> SetCommands
$cfrom :: forall x. SetCommands -> Rep SetCommands x
Generic)

-- | Parameter of Function getActiveSessions
data GetActiveSessions
  = -- | Returns all active sessions of the current user
    GetActiveSessions
      {
      }
  deriving (Int -> GetActiveSessions -> ShowS
[GetActiveSessions] -> ShowS
GetActiveSessions -> String
(Int -> GetActiveSessions -> ShowS)
-> (GetActiveSessions -> String)
-> ([GetActiveSessions] -> ShowS)
-> Show GetActiveSessions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetActiveSessions] -> ShowS
$cshowList :: [GetActiveSessions] -> ShowS
show :: GetActiveSessions -> String
$cshow :: GetActiveSessions -> String
showsPrec :: Int -> GetActiveSessions -> ShowS
$cshowsPrec :: Int -> GetActiveSessions -> ShowS
Show, GetActiveSessions -> GetActiveSessions -> Bool
(GetActiveSessions -> GetActiveSessions -> Bool)
-> (GetActiveSessions -> GetActiveSessions -> Bool)
-> Eq GetActiveSessions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetActiveSessions -> GetActiveSessions -> Bool
$c/= :: GetActiveSessions -> GetActiveSessions -> Bool
== :: GetActiveSessions -> GetActiveSessions -> Bool
$c== :: GetActiveSessions -> GetActiveSessions -> Bool
Eq, (forall x. GetActiveSessions -> Rep GetActiveSessions x)
-> (forall x. Rep GetActiveSessions x -> GetActiveSessions)
-> Generic GetActiveSessions
forall x. Rep GetActiveSessions x -> GetActiveSessions
forall x. GetActiveSessions -> Rep GetActiveSessions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetActiveSessions x -> GetActiveSessions
$cfrom :: forall x. GetActiveSessions -> Rep GetActiveSessions x
Generic)

-- | Parameter of Function terminateSession
data TerminateSession
  = -- | Terminates a session of the current user
    TerminateSession
      { -- | Session identifier
        TerminateSession -> I64
session_id :: I64
      }
  deriving (Int -> TerminateSession -> ShowS
[TerminateSession] -> ShowS
TerminateSession -> String
(Int -> TerminateSession -> ShowS)
-> (TerminateSession -> String)
-> ([TerminateSession] -> ShowS)
-> Show TerminateSession
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminateSession] -> ShowS
$cshowList :: [TerminateSession] -> ShowS
show :: TerminateSession -> String
$cshow :: TerminateSession -> String
showsPrec :: Int -> TerminateSession -> ShowS
$cshowsPrec :: Int -> TerminateSession -> ShowS
Show, TerminateSession -> TerminateSession -> Bool
(TerminateSession -> TerminateSession -> Bool)
-> (TerminateSession -> TerminateSession -> Bool)
-> Eq TerminateSession
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateSession -> TerminateSession -> Bool
$c/= :: TerminateSession -> TerminateSession -> Bool
== :: TerminateSession -> TerminateSession -> Bool
$c== :: TerminateSession -> TerminateSession -> Bool
Eq, (forall x. TerminateSession -> Rep TerminateSession x)
-> (forall x. Rep TerminateSession x -> TerminateSession)
-> Generic TerminateSession
forall x. Rep TerminateSession x -> TerminateSession
forall x. TerminateSession -> Rep TerminateSession x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TerminateSession x -> TerminateSession
$cfrom :: forall x. TerminateSession -> Rep TerminateSession x
Generic)

-- | Parameter of Function terminateAllOtherSessions
data TerminateAllOtherSessions
  = -- | Terminates all other sessions of the current user
    TerminateAllOtherSessions
      {
      }
  deriving (Int -> TerminateAllOtherSessions -> ShowS
[TerminateAllOtherSessions] -> ShowS
TerminateAllOtherSessions -> String
(Int -> TerminateAllOtherSessions -> ShowS)
-> (TerminateAllOtherSessions -> String)
-> ([TerminateAllOtherSessions] -> ShowS)
-> Show TerminateAllOtherSessions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TerminateAllOtherSessions] -> ShowS
$cshowList :: [TerminateAllOtherSessions] -> ShowS
show :: TerminateAllOtherSessions -> String
$cshow :: TerminateAllOtherSessions -> String
showsPrec :: Int -> TerminateAllOtherSessions -> ShowS
$cshowsPrec :: Int -> TerminateAllOtherSessions -> ShowS
Show, TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool
(TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool)
-> (TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool)
-> Eq TerminateAllOtherSessions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool
$c/= :: TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool
== :: TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool
$c== :: TerminateAllOtherSessions -> TerminateAllOtherSessions -> Bool
Eq, (forall x.
 TerminateAllOtherSessions -> Rep TerminateAllOtherSessions x)
-> (forall x.
    Rep TerminateAllOtherSessions x -> TerminateAllOtherSessions)
-> Generic TerminateAllOtherSessions
forall x.
Rep TerminateAllOtherSessions x -> TerminateAllOtherSessions
forall x.
TerminateAllOtherSessions -> Rep TerminateAllOtherSessions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TerminateAllOtherSessions x -> TerminateAllOtherSessions
$cfrom :: forall x.
TerminateAllOtherSessions -> Rep TerminateAllOtherSessions x
Generic)

-- | Parameter of Function getConnectedWebsites
data GetConnectedWebsites
  = -- | Returns all website where the current user used Telegram to log in
    GetConnectedWebsites
      {
      }
  deriving (Int -> GetConnectedWebsites -> ShowS
[GetConnectedWebsites] -> ShowS
GetConnectedWebsites -> String
(Int -> GetConnectedWebsites -> ShowS)
-> (GetConnectedWebsites -> String)
-> ([GetConnectedWebsites] -> ShowS)
-> Show GetConnectedWebsites
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetConnectedWebsites] -> ShowS
$cshowList :: [GetConnectedWebsites] -> ShowS
show :: GetConnectedWebsites -> String
$cshow :: GetConnectedWebsites -> String
showsPrec :: Int -> GetConnectedWebsites -> ShowS
$cshowsPrec :: Int -> GetConnectedWebsites -> ShowS
Show, GetConnectedWebsites -> GetConnectedWebsites -> Bool
(GetConnectedWebsites -> GetConnectedWebsites -> Bool)
-> (GetConnectedWebsites -> GetConnectedWebsites -> Bool)
-> Eq GetConnectedWebsites
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetConnectedWebsites -> GetConnectedWebsites -> Bool
$c/= :: GetConnectedWebsites -> GetConnectedWebsites -> Bool
== :: GetConnectedWebsites -> GetConnectedWebsites -> Bool
$c== :: GetConnectedWebsites -> GetConnectedWebsites -> Bool
Eq, (forall x. GetConnectedWebsites -> Rep GetConnectedWebsites x)
-> (forall x. Rep GetConnectedWebsites x -> GetConnectedWebsites)
-> Generic GetConnectedWebsites
forall x. Rep GetConnectedWebsites x -> GetConnectedWebsites
forall x. GetConnectedWebsites -> Rep GetConnectedWebsites x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetConnectedWebsites x -> GetConnectedWebsites
$cfrom :: forall x. GetConnectedWebsites -> Rep GetConnectedWebsites x
Generic)

-- | Parameter of Function disconnectWebsite
data DisconnectWebsite
  = -- | Disconnects website from the current user's Telegram account
    DisconnectWebsite
      { -- | Website identifier
        DisconnectWebsite -> I64
website_id :: I64
      }
  deriving (Int -> DisconnectWebsite -> ShowS
[DisconnectWebsite] -> ShowS
DisconnectWebsite -> String
(Int -> DisconnectWebsite -> ShowS)
-> (DisconnectWebsite -> String)
-> ([DisconnectWebsite] -> ShowS)
-> Show DisconnectWebsite
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisconnectWebsite] -> ShowS
$cshowList :: [DisconnectWebsite] -> ShowS
show :: DisconnectWebsite -> String
$cshow :: DisconnectWebsite -> String
showsPrec :: Int -> DisconnectWebsite -> ShowS
$cshowsPrec :: Int -> DisconnectWebsite -> ShowS
Show, DisconnectWebsite -> DisconnectWebsite -> Bool
(DisconnectWebsite -> DisconnectWebsite -> Bool)
-> (DisconnectWebsite -> DisconnectWebsite -> Bool)
-> Eq DisconnectWebsite
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisconnectWebsite -> DisconnectWebsite -> Bool
$c/= :: DisconnectWebsite -> DisconnectWebsite -> Bool
== :: DisconnectWebsite -> DisconnectWebsite -> Bool
$c== :: DisconnectWebsite -> DisconnectWebsite -> Bool
Eq, (forall x. DisconnectWebsite -> Rep DisconnectWebsite x)
-> (forall x. Rep DisconnectWebsite x -> DisconnectWebsite)
-> Generic DisconnectWebsite
forall x. Rep DisconnectWebsite x -> DisconnectWebsite
forall x. DisconnectWebsite -> Rep DisconnectWebsite x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisconnectWebsite x -> DisconnectWebsite
$cfrom :: forall x. DisconnectWebsite -> Rep DisconnectWebsite x
Generic)

-- | Parameter of Function disconnectAllWebsites
data DisconnectAllWebsites
  = -- | Disconnects all websites from the current user's Telegram account
    DisconnectAllWebsites
      {
      }
  deriving (Int -> DisconnectAllWebsites -> ShowS
[DisconnectAllWebsites] -> ShowS
DisconnectAllWebsites -> String
(Int -> DisconnectAllWebsites -> ShowS)
-> (DisconnectAllWebsites -> String)
-> ([DisconnectAllWebsites] -> ShowS)
-> Show DisconnectAllWebsites
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisconnectAllWebsites] -> ShowS
$cshowList :: [DisconnectAllWebsites] -> ShowS
show :: DisconnectAllWebsites -> String
$cshow :: DisconnectAllWebsites -> String
showsPrec :: Int -> DisconnectAllWebsites -> ShowS
$cshowsPrec :: Int -> DisconnectAllWebsites -> ShowS
Show, DisconnectAllWebsites -> DisconnectAllWebsites -> Bool
(DisconnectAllWebsites -> DisconnectAllWebsites -> Bool)
-> (DisconnectAllWebsites -> DisconnectAllWebsites -> Bool)
-> Eq DisconnectAllWebsites
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisconnectAllWebsites -> DisconnectAllWebsites -> Bool
$c/= :: DisconnectAllWebsites -> DisconnectAllWebsites -> Bool
== :: DisconnectAllWebsites -> DisconnectAllWebsites -> Bool
$c== :: DisconnectAllWebsites -> DisconnectAllWebsites -> Bool
Eq, (forall x. DisconnectAllWebsites -> Rep DisconnectAllWebsites x)
-> (forall x. Rep DisconnectAllWebsites x -> DisconnectAllWebsites)
-> Generic DisconnectAllWebsites
forall x. Rep DisconnectAllWebsites x -> DisconnectAllWebsites
forall x. DisconnectAllWebsites -> Rep DisconnectAllWebsites x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisconnectAllWebsites x -> DisconnectAllWebsites
$cfrom :: forall x. DisconnectAllWebsites -> Rep DisconnectAllWebsites x
Generic)

-- | Parameter of Function setSupergroupUsername
data SetSupergroupUsername
  = -- | Changes the username of a supergroup or channel, requires owner privileges in the supergroup or channel
    SetSupergroupUsername
      { -- | Identifier of the supergroup or channel
        SetSupergroupUsername -> Int
supergroup_id :: I32,
        -- | New value of the username. Use an empty string to remove the username
        SetSupergroupUsername -> T
username :: T
      }
  deriving (Int -> SetSupergroupUsername -> ShowS
[SetSupergroupUsername] -> ShowS
SetSupergroupUsername -> String
(Int -> SetSupergroupUsername -> ShowS)
-> (SetSupergroupUsername -> String)
-> ([SetSupergroupUsername] -> ShowS)
-> Show SetSupergroupUsername
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetSupergroupUsername] -> ShowS
$cshowList :: [SetSupergroupUsername] -> ShowS
show :: SetSupergroupUsername -> String
$cshow :: SetSupergroupUsername -> String
showsPrec :: Int -> SetSupergroupUsername -> ShowS
$cshowsPrec :: Int -> SetSupergroupUsername -> ShowS
Show, SetSupergroupUsername -> SetSupergroupUsername -> Bool
(SetSupergroupUsername -> SetSupergroupUsername -> Bool)
-> (SetSupergroupUsername -> SetSupergroupUsername -> Bool)
-> Eq SetSupergroupUsername
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetSupergroupUsername -> SetSupergroupUsername -> Bool
$c/= :: SetSupergroupUsername -> SetSupergroupUsername -> Bool
== :: SetSupergroupUsername -> SetSupergroupUsername -> Bool
$c== :: SetSupergroupUsername -> SetSupergroupUsername -> Bool
Eq, (forall x. SetSupergroupUsername -> Rep SetSupergroupUsername x)
-> (forall x. Rep SetSupergroupUsername x -> SetSupergroupUsername)
-> Generic SetSupergroupUsername
forall x. Rep SetSupergroupUsername x -> SetSupergroupUsername
forall x. SetSupergroupUsername -> Rep SetSupergroupUsername x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetSupergroupUsername x -> SetSupergroupUsername
$cfrom :: forall x. SetSupergroupUsername -> Rep SetSupergroupUsername x
Generic)

-- | Parameter of Function setSupergroupStickerSet
data SetSupergroupStickerSet
  = -- | Changes the sticker set of a supergroup; requires can_change_info rights
    SetSupergroupStickerSet
      { -- | Identifier of the supergroup
        SetSupergroupStickerSet -> Int
supergroup_id :: I32,
        -- | New value of the supergroup sticker set identifier. Use 0 to remove the supergroup sticker set
        SetSupergroupStickerSet -> I64
sticker_set_id :: I64
      }
  deriving (Int -> SetSupergroupStickerSet -> ShowS
[SetSupergroupStickerSet] -> ShowS
SetSupergroupStickerSet -> String
(Int -> SetSupergroupStickerSet -> ShowS)
-> (SetSupergroupStickerSet -> String)
-> ([SetSupergroupStickerSet] -> ShowS)
-> Show SetSupergroupStickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetSupergroupStickerSet] -> ShowS
$cshowList :: [SetSupergroupStickerSet] -> ShowS
show :: SetSupergroupStickerSet -> String
$cshow :: SetSupergroupStickerSet -> String
showsPrec :: Int -> SetSupergroupStickerSet -> ShowS
$cshowsPrec :: Int -> SetSupergroupStickerSet -> ShowS
Show, SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool
(SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool)
-> (SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool)
-> Eq SetSupergroupStickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool
$c/= :: SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool
== :: SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool
$c== :: SetSupergroupStickerSet -> SetSupergroupStickerSet -> Bool
Eq, (forall x.
 SetSupergroupStickerSet -> Rep SetSupergroupStickerSet x)
-> (forall x.
    Rep SetSupergroupStickerSet x -> SetSupergroupStickerSet)
-> Generic SetSupergroupStickerSet
forall x. Rep SetSupergroupStickerSet x -> SetSupergroupStickerSet
forall x. SetSupergroupStickerSet -> Rep SetSupergroupStickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetSupergroupStickerSet x -> SetSupergroupStickerSet
$cfrom :: forall x. SetSupergroupStickerSet -> Rep SetSupergroupStickerSet x
Generic)

-- | Parameter of Function toggleSupergroupSignMessages
data ToggleSupergroupSignMessages
  = -- | Toggles sender signatures messages sent in a channel; requires can_change_info rights
    ToggleSupergroupSignMessages
      { -- | Identifier of the channel
        ToggleSupergroupSignMessages -> Int
supergroup_id :: I32,
        -- | New value of sign_messages
        ToggleSupergroupSignMessages -> Bool
sign_messages :: Bool
      }
  deriving (Int -> ToggleSupergroupSignMessages -> ShowS
[ToggleSupergroupSignMessages] -> ShowS
ToggleSupergroupSignMessages -> String
(Int -> ToggleSupergroupSignMessages -> ShowS)
-> (ToggleSupergroupSignMessages -> String)
-> ([ToggleSupergroupSignMessages] -> ShowS)
-> Show ToggleSupergroupSignMessages
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToggleSupergroupSignMessages] -> ShowS
$cshowList :: [ToggleSupergroupSignMessages] -> ShowS
show :: ToggleSupergroupSignMessages -> String
$cshow :: ToggleSupergroupSignMessages -> String
showsPrec :: Int -> ToggleSupergroupSignMessages -> ShowS
$cshowsPrec :: Int -> ToggleSupergroupSignMessages -> ShowS
Show, ToggleSupergroupSignMessages
-> ToggleSupergroupSignMessages -> Bool
(ToggleSupergroupSignMessages
 -> ToggleSupergroupSignMessages -> Bool)
-> (ToggleSupergroupSignMessages
    -> ToggleSupergroupSignMessages -> Bool)
-> Eq ToggleSupergroupSignMessages
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToggleSupergroupSignMessages
-> ToggleSupergroupSignMessages -> Bool
$c/= :: ToggleSupergroupSignMessages
-> ToggleSupergroupSignMessages -> Bool
== :: ToggleSupergroupSignMessages
-> ToggleSupergroupSignMessages -> Bool
$c== :: ToggleSupergroupSignMessages
-> ToggleSupergroupSignMessages -> Bool
Eq, (forall x.
 ToggleSupergroupSignMessages -> Rep ToggleSupergroupSignMessages x)
-> (forall x.
    Rep ToggleSupergroupSignMessages x -> ToggleSupergroupSignMessages)
-> Generic ToggleSupergroupSignMessages
forall x.
Rep ToggleSupergroupSignMessages x -> ToggleSupergroupSignMessages
forall x.
ToggleSupergroupSignMessages -> Rep ToggleSupergroupSignMessages x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ToggleSupergroupSignMessages x -> ToggleSupergroupSignMessages
$cfrom :: forall x.
ToggleSupergroupSignMessages -> Rep ToggleSupergroupSignMessages x
Generic)

-- | Parameter of Function toggleSupergroupIsAllHistoryAvailable
data ToggleSupergroupIsAllHistoryAvailable
  = -- | Toggles whether the message history of a supergroup is available to new members; requires can_change_info rights
    ToggleSupergroupIsAllHistoryAvailable
      { -- | The identifier of the supergroup
        ToggleSupergroupIsAllHistoryAvailable -> Int
supergroup_id :: I32,
        -- | The new value of is_all_history_available
        ToggleSupergroupIsAllHistoryAvailable -> Bool
is_all_history_available :: Bool
      }
  deriving (Int -> ToggleSupergroupIsAllHistoryAvailable -> ShowS
[ToggleSupergroupIsAllHistoryAvailable] -> ShowS
ToggleSupergroupIsAllHistoryAvailable -> String
(Int -> ToggleSupergroupIsAllHistoryAvailable -> ShowS)
-> (ToggleSupergroupIsAllHistoryAvailable -> String)
-> ([ToggleSupergroupIsAllHistoryAvailable] -> ShowS)
-> Show ToggleSupergroupIsAllHistoryAvailable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ToggleSupergroupIsAllHistoryAvailable] -> ShowS
$cshowList :: [ToggleSupergroupIsAllHistoryAvailable] -> ShowS
show :: ToggleSupergroupIsAllHistoryAvailable -> String
$cshow :: ToggleSupergroupIsAllHistoryAvailable -> String
showsPrec :: Int -> ToggleSupergroupIsAllHistoryAvailable -> ShowS
$cshowsPrec :: Int -> ToggleSupergroupIsAllHistoryAvailable -> ShowS
Show, ToggleSupergroupIsAllHistoryAvailable
-> ToggleSupergroupIsAllHistoryAvailable -> Bool
(ToggleSupergroupIsAllHistoryAvailable
 -> ToggleSupergroupIsAllHistoryAvailable -> Bool)
-> (ToggleSupergroupIsAllHistoryAvailable
    -> ToggleSupergroupIsAllHistoryAvailable -> Bool)
-> Eq ToggleSupergroupIsAllHistoryAvailable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ToggleSupergroupIsAllHistoryAvailable
-> ToggleSupergroupIsAllHistoryAvailable -> Bool
$c/= :: ToggleSupergroupIsAllHistoryAvailable
-> ToggleSupergroupIsAllHistoryAvailable -> Bool
== :: ToggleSupergroupIsAllHistoryAvailable
-> ToggleSupergroupIsAllHistoryAvailable -> Bool
$c== :: ToggleSupergroupIsAllHistoryAvailable
-> ToggleSupergroupIsAllHistoryAvailable -> Bool
Eq, (forall x.
 ToggleSupergroupIsAllHistoryAvailable
 -> Rep ToggleSupergroupIsAllHistoryAvailable x)
-> (forall x.
    Rep ToggleSupergroupIsAllHistoryAvailable x
    -> ToggleSupergroupIsAllHistoryAvailable)
-> Generic ToggleSupergroupIsAllHistoryAvailable
forall x.
Rep ToggleSupergroupIsAllHistoryAvailable x
-> ToggleSupergroupIsAllHistoryAvailable
forall x.
ToggleSupergroupIsAllHistoryAvailable
-> Rep ToggleSupergroupIsAllHistoryAvailable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ToggleSupergroupIsAllHistoryAvailable x
-> ToggleSupergroupIsAllHistoryAvailable
$cfrom :: forall x.
ToggleSupergroupIsAllHistoryAvailable
-> Rep ToggleSupergroupIsAllHistoryAvailable x
Generic)

-- | Parameter of Function reportSupergroupSpam
data ReportSupergroupSpam
  = -- | Reports some messages from a user in a supergroup as spam; requires administrator rights in the supergroup
    ReportSupergroupSpam
      { -- | Supergroup identifier
        ReportSupergroupSpam -> Int
supergroup_id :: I32,
        -- | User identifier
        ReportSupergroupSpam -> Int
user_id :: I32,
        -- | Identifiers of messages sent in the supergroup by the user. This list must be non-empty
        ReportSupergroupSpam -> [Int]
message_ids :: ([]) (I53)
      }
  deriving (Int -> ReportSupergroupSpam -> ShowS
[ReportSupergroupSpam] -> ShowS
ReportSupergroupSpam -> String
(Int -> ReportSupergroupSpam -> ShowS)
-> (ReportSupergroupSpam -> String)
-> ([ReportSupergroupSpam] -> ShowS)
-> Show ReportSupergroupSpam
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportSupergroupSpam] -> ShowS
$cshowList :: [ReportSupergroupSpam] -> ShowS
show :: ReportSupergroupSpam -> String
$cshow :: ReportSupergroupSpam -> String
showsPrec :: Int -> ReportSupergroupSpam -> ShowS
$cshowsPrec :: Int -> ReportSupergroupSpam -> ShowS
Show, ReportSupergroupSpam -> ReportSupergroupSpam -> Bool
(ReportSupergroupSpam -> ReportSupergroupSpam -> Bool)
-> (ReportSupergroupSpam -> ReportSupergroupSpam -> Bool)
-> Eq ReportSupergroupSpam
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportSupergroupSpam -> ReportSupergroupSpam -> Bool
$c/= :: ReportSupergroupSpam -> ReportSupergroupSpam -> Bool
== :: ReportSupergroupSpam -> ReportSupergroupSpam -> Bool
$c== :: ReportSupergroupSpam -> ReportSupergroupSpam -> Bool
Eq, (forall x. ReportSupergroupSpam -> Rep ReportSupergroupSpam x)
-> (forall x. Rep ReportSupergroupSpam x -> ReportSupergroupSpam)
-> Generic ReportSupergroupSpam
forall x. Rep ReportSupergroupSpam x -> ReportSupergroupSpam
forall x. ReportSupergroupSpam -> Rep ReportSupergroupSpam x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReportSupergroupSpam x -> ReportSupergroupSpam
$cfrom :: forall x. ReportSupergroupSpam -> Rep ReportSupergroupSpam x
Generic)

-- | Parameter of Function getSupergroupMembers
data GetSupergroupMembers
  = -- | Returns information about members or banned users in a supergroup or channel. Can be used only if SupergroupFullInfo.can_get_members == true; additionally, administrator privileges may be required for some filters
    GetSupergroupMembers
      { -- | Identifier of the supergroup or channel
        GetSupergroupMembers -> Int
supergroup_id :: I32,
        -- | The type of users to return. By default, supergroupMembersRecent
        GetSupergroupMembers -> SupergroupMembersFilter
filter :: SupergroupMembersFilter,
        -- | Number of users to skip
        GetSupergroupMembers -> Int
offset :: I32,
        -- | The maximum number of users be returned; up to 200
        GetSupergroupMembers -> Int
limit :: I32
      }
  deriving (Int -> GetSupergroupMembers -> ShowS
[GetSupergroupMembers] -> ShowS
GetSupergroupMembers -> String
(Int -> GetSupergroupMembers -> ShowS)
-> (GetSupergroupMembers -> String)
-> ([GetSupergroupMembers] -> ShowS)
-> Show GetSupergroupMembers
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSupergroupMembers] -> ShowS
$cshowList :: [GetSupergroupMembers] -> ShowS
show :: GetSupergroupMembers -> String
$cshow :: GetSupergroupMembers -> String
showsPrec :: Int -> GetSupergroupMembers -> ShowS
$cshowsPrec :: Int -> GetSupergroupMembers -> ShowS
Show, GetSupergroupMembers -> GetSupergroupMembers -> Bool
(GetSupergroupMembers -> GetSupergroupMembers -> Bool)
-> (GetSupergroupMembers -> GetSupergroupMembers -> Bool)
-> Eq GetSupergroupMembers
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSupergroupMembers -> GetSupergroupMembers -> Bool
$c/= :: GetSupergroupMembers -> GetSupergroupMembers -> Bool
== :: GetSupergroupMembers -> GetSupergroupMembers -> Bool
$c== :: GetSupergroupMembers -> GetSupergroupMembers -> Bool
Eq, (forall x. GetSupergroupMembers -> Rep GetSupergroupMembers x)
-> (forall x. Rep GetSupergroupMembers x -> GetSupergroupMembers)
-> Generic GetSupergroupMembers
forall x. Rep GetSupergroupMembers x -> GetSupergroupMembers
forall x. GetSupergroupMembers -> Rep GetSupergroupMembers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSupergroupMembers x -> GetSupergroupMembers
$cfrom :: forall x. GetSupergroupMembers -> Rep GetSupergroupMembers x
Generic)

-- | Parameter of Function deleteSupergroup
data DeleteSupergroup
  = -- | Deletes a supergroup or channel along with all messages in the corresponding chat. This will release the supergroup or channel username and remove all members; requires owner privileges in the supergroup or channel. Chats with more than 1000 members can't be deleted using this method
    DeleteSupergroup
      { -- | Identifier of the supergroup or channel
        DeleteSupergroup -> Int
supergroup_id :: I32
      }
  deriving (Int -> DeleteSupergroup -> ShowS
[DeleteSupergroup] -> ShowS
DeleteSupergroup -> String
(Int -> DeleteSupergroup -> ShowS)
-> (DeleteSupergroup -> String)
-> ([DeleteSupergroup] -> ShowS)
-> Show DeleteSupergroup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSupergroup] -> ShowS
$cshowList :: [DeleteSupergroup] -> ShowS
show :: DeleteSupergroup -> String
$cshow :: DeleteSupergroup -> String
showsPrec :: Int -> DeleteSupergroup -> ShowS
$cshowsPrec :: Int -> DeleteSupergroup -> ShowS
Show, DeleteSupergroup -> DeleteSupergroup -> Bool
(DeleteSupergroup -> DeleteSupergroup -> Bool)
-> (DeleteSupergroup -> DeleteSupergroup -> Bool)
-> Eq DeleteSupergroup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSupergroup -> DeleteSupergroup -> Bool
$c/= :: DeleteSupergroup -> DeleteSupergroup -> Bool
== :: DeleteSupergroup -> DeleteSupergroup -> Bool
$c== :: DeleteSupergroup -> DeleteSupergroup -> Bool
Eq, (forall x. DeleteSupergroup -> Rep DeleteSupergroup x)
-> (forall x. Rep DeleteSupergroup x -> DeleteSupergroup)
-> Generic DeleteSupergroup
forall x. Rep DeleteSupergroup x -> DeleteSupergroup
forall x. DeleteSupergroup -> Rep DeleteSupergroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSupergroup x -> DeleteSupergroup
$cfrom :: forall x. DeleteSupergroup -> Rep DeleteSupergroup x
Generic)

-- | Parameter of Function closeSecretChat
data CloseSecretChat
  = -- | Closes a secret chat, effectively transferring its state to secretChatStateClosed
    CloseSecretChat
      { -- | Secret chat identifier
        CloseSecretChat -> Int
secret_chat_id :: I32
      }
  deriving (Int -> CloseSecretChat -> ShowS
[CloseSecretChat] -> ShowS
CloseSecretChat -> String
(Int -> CloseSecretChat -> ShowS)
-> (CloseSecretChat -> String)
-> ([CloseSecretChat] -> ShowS)
-> Show CloseSecretChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CloseSecretChat] -> ShowS
$cshowList :: [CloseSecretChat] -> ShowS
show :: CloseSecretChat -> String
$cshow :: CloseSecretChat -> String
showsPrec :: Int -> CloseSecretChat -> ShowS
$cshowsPrec :: Int -> CloseSecretChat -> ShowS
Show, CloseSecretChat -> CloseSecretChat -> Bool
(CloseSecretChat -> CloseSecretChat -> Bool)
-> (CloseSecretChat -> CloseSecretChat -> Bool)
-> Eq CloseSecretChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CloseSecretChat -> CloseSecretChat -> Bool
$c/= :: CloseSecretChat -> CloseSecretChat -> Bool
== :: CloseSecretChat -> CloseSecretChat -> Bool
$c== :: CloseSecretChat -> CloseSecretChat -> Bool
Eq, (forall x. CloseSecretChat -> Rep CloseSecretChat x)
-> (forall x. Rep CloseSecretChat x -> CloseSecretChat)
-> Generic CloseSecretChat
forall x. Rep CloseSecretChat x -> CloseSecretChat
forall x. CloseSecretChat -> Rep CloseSecretChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CloseSecretChat x -> CloseSecretChat
$cfrom :: forall x. CloseSecretChat -> Rep CloseSecretChat x
Generic)

-- | Parameter of Function getChatEventLog
data GetChatEventLog
  = -- | Returns a list of service actions taken by chat members and administrators in the last 48 hours. Available only for supergroups and channels. Requires administrator rights. Returns results in reverse chronological order (i. e., in order of decreasing event_id)
    GetChatEventLog
      { -- | Chat identifier
        GetChatEventLog -> Int
chat_id :: I53,
        -- | Search query by which to filter events
        GetChatEventLog -> T
query :: T,
        -- | Identifier of an event from which to return results. Use 0 to get results from the latest events
        GetChatEventLog -> I64
from_event_id :: I64,
        -- | The maximum number of events to return; up to 100
        GetChatEventLog -> Int
limit :: I32,
        -- | The types of events to return. By default, all types will be returned
        GetChatEventLog -> ChatEventLogFilters
filters :: ChatEventLogFilters,
        -- | User identifiers by which to filter events. By default, events relating to all users will be returned
        GetChatEventLog -> [Int]
user_ids :: ([]) (I32)
      }
  deriving (Int -> GetChatEventLog -> ShowS
[GetChatEventLog] -> ShowS
GetChatEventLog -> String
(Int -> GetChatEventLog -> ShowS)
-> (GetChatEventLog -> String)
-> ([GetChatEventLog] -> ShowS)
-> Show GetChatEventLog
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatEventLog] -> ShowS
$cshowList :: [GetChatEventLog] -> ShowS
show :: GetChatEventLog -> String
$cshow :: GetChatEventLog -> String
showsPrec :: Int -> GetChatEventLog -> ShowS
$cshowsPrec :: Int -> GetChatEventLog -> ShowS
Show, GetChatEventLog -> GetChatEventLog -> Bool
(GetChatEventLog -> GetChatEventLog -> Bool)
-> (GetChatEventLog -> GetChatEventLog -> Bool)
-> Eq GetChatEventLog
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatEventLog -> GetChatEventLog -> Bool
$c/= :: GetChatEventLog -> GetChatEventLog -> Bool
== :: GetChatEventLog -> GetChatEventLog -> Bool
$c== :: GetChatEventLog -> GetChatEventLog -> Bool
Eq, (forall x. GetChatEventLog -> Rep GetChatEventLog x)
-> (forall x. Rep GetChatEventLog x -> GetChatEventLog)
-> Generic GetChatEventLog
forall x. Rep GetChatEventLog x -> GetChatEventLog
forall x. GetChatEventLog -> Rep GetChatEventLog x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatEventLog x -> GetChatEventLog
$cfrom :: forall x. GetChatEventLog -> Rep GetChatEventLog x
Generic)

-- | Parameter of Function getPaymentForm
data GetPaymentForm
  = -- | Returns an invoice payment form. This method should be called when the user presses inlineKeyboardButtonBuy
    GetPaymentForm
      { -- | Chat identifier of the Invoice message
        GetPaymentForm -> Int
chat_id :: I53,
        -- | Message identifier
        GetPaymentForm -> Int
message_id :: I53
      }
  deriving (Int -> GetPaymentForm -> ShowS
[GetPaymentForm] -> ShowS
GetPaymentForm -> String
(Int -> GetPaymentForm -> ShowS)
-> (GetPaymentForm -> String)
-> ([GetPaymentForm] -> ShowS)
-> Show GetPaymentForm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPaymentForm] -> ShowS
$cshowList :: [GetPaymentForm] -> ShowS
show :: GetPaymentForm -> String
$cshow :: GetPaymentForm -> String
showsPrec :: Int -> GetPaymentForm -> ShowS
$cshowsPrec :: Int -> GetPaymentForm -> ShowS
Show, GetPaymentForm -> GetPaymentForm -> Bool
(GetPaymentForm -> GetPaymentForm -> Bool)
-> (GetPaymentForm -> GetPaymentForm -> Bool) -> Eq GetPaymentForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPaymentForm -> GetPaymentForm -> Bool
$c/= :: GetPaymentForm -> GetPaymentForm -> Bool
== :: GetPaymentForm -> GetPaymentForm -> Bool
$c== :: GetPaymentForm -> GetPaymentForm -> Bool
Eq, (forall x. GetPaymentForm -> Rep GetPaymentForm x)
-> (forall x. Rep GetPaymentForm x -> GetPaymentForm)
-> Generic GetPaymentForm
forall x. Rep GetPaymentForm x -> GetPaymentForm
forall x. GetPaymentForm -> Rep GetPaymentForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPaymentForm x -> GetPaymentForm
$cfrom :: forall x. GetPaymentForm -> Rep GetPaymentForm x
Generic)

-- | Parameter of Function validateOrderInfo
data ValidateOrderInfo
  = -- | Validates the order information provided by a user and returns the available shipping options for a flexible invoice
    ValidateOrderInfo
      { -- | Chat identifier of the Invoice message
        ValidateOrderInfo -> Int
chat_id :: I53,
        -- | Message identifier
        ValidateOrderInfo -> Int
message_id :: I53,
        -- | The order information, provided by the user
        ValidateOrderInfo -> OrderInfo
order_info :: OrderInfo,
        -- | True, if the order information can be saved
        ValidateOrderInfo -> Bool
allow_save :: Bool
      }
  deriving (Int -> ValidateOrderInfo -> ShowS
[ValidateOrderInfo] -> ShowS
ValidateOrderInfo -> String
(Int -> ValidateOrderInfo -> ShowS)
-> (ValidateOrderInfo -> String)
-> ([ValidateOrderInfo] -> ShowS)
-> Show ValidateOrderInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ValidateOrderInfo] -> ShowS
$cshowList :: [ValidateOrderInfo] -> ShowS
show :: ValidateOrderInfo -> String
$cshow :: ValidateOrderInfo -> String
showsPrec :: Int -> ValidateOrderInfo -> ShowS
$cshowsPrec :: Int -> ValidateOrderInfo -> ShowS
Show, ValidateOrderInfo -> ValidateOrderInfo -> Bool
(ValidateOrderInfo -> ValidateOrderInfo -> Bool)
-> (ValidateOrderInfo -> ValidateOrderInfo -> Bool)
-> Eq ValidateOrderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ValidateOrderInfo -> ValidateOrderInfo -> Bool
$c/= :: ValidateOrderInfo -> ValidateOrderInfo -> Bool
== :: ValidateOrderInfo -> ValidateOrderInfo -> Bool
$c== :: ValidateOrderInfo -> ValidateOrderInfo -> Bool
Eq, (forall x. ValidateOrderInfo -> Rep ValidateOrderInfo x)
-> (forall x. Rep ValidateOrderInfo x -> ValidateOrderInfo)
-> Generic ValidateOrderInfo
forall x. Rep ValidateOrderInfo x -> ValidateOrderInfo
forall x. ValidateOrderInfo -> Rep ValidateOrderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ValidateOrderInfo x -> ValidateOrderInfo
$cfrom :: forall x. ValidateOrderInfo -> Rep ValidateOrderInfo x
Generic)

-- | Parameter of Function sendPaymentForm
data SendPaymentForm
  = -- | Sends a filled-out payment form to the bot for final verification
    SendPaymentForm
      { -- | Chat identifier of the Invoice message
        SendPaymentForm -> Int
chat_id :: I53,
        -- | Message identifier
        SendPaymentForm -> Int
message_id :: I53,
        -- | Identifier returned by ValidateOrderInfo, or an empty string
        SendPaymentForm -> T
order_info_id :: T,
        -- | Identifier of a chosen shipping option, if applicable
        SendPaymentForm -> T
shipping_option_id :: T,
        -- | The credentials chosen by user for payment
        SendPaymentForm -> InputCredentials
credentials :: InputCredentials
      }
  deriving (Int -> SendPaymentForm -> ShowS
[SendPaymentForm] -> ShowS
SendPaymentForm -> String
(Int -> SendPaymentForm -> ShowS)
-> (SendPaymentForm -> String)
-> ([SendPaymentForm] -> ShowS)
-> Show SendPaymentForm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendPaymentForm] -> ShowS
$cshowList :: [SendPaymentForm] -> ShowS
show :: SendPaymentForm -> String
$cshow :: SendPaymentForm -> String
showsPrec :: Int -> SendPaymentForm -> ShowS
$cshowsPrec :: Int -> SendPaymentForm -> ShowS
Show, SendPaymentForm -> SendPaymentForm -> Bool
(SendPaymentForm -> SendPaymentForm -> Bool)
-> (SendPaymentForm -> SendPaymentForm -> Bool)
-> Eq SendPaymentForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendPaymentForm -> SendPaymentForm -> Bool
$c/= :: SendPaymentForm -> SendPaymentForm -> Bool
== :: SendPaymentForm -> SendPaymentForm -> Bool
$c== :: SendPaymentForm -> SendPaymentForm -> Bool
Eq, (forall x. SendPaymentForm -> Rep SendPaymentForm x)
-> (forall x. Rep SendPaymentForm x -> SendPaymentForm)
-> Generic SendPaymentForm
forall x. Rep SendPaymentForm x -> SendPaymentForm
forall x. SendPaymentForm -> Rep SendPaymentForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendPaymentForm x -> SendPaymentForm
$cfrom :: forall x. SendPaymentForm -> Rep SendPaymentForm x
Generic)

-- | Parameter of Function getPaymentReceipt
data GetPaymentReceipt
  = -- | Returns information about a successful payment
    GetPaymentReceipt
      { -- | Chat identifier of the PaymentSuccessful message
        GetPaymentReceipt -> Int
chat_id :: I53,
        -- | Message identifier
        GetPaymentReceipt -> Int
message_id :: I53
      }
  deriving (Int -> GetPaymentReceipt -> ShowS
[GetPaymentReceipt] -> ShowS
GetPaymentReceipt -> String
(Int -> GetPaymentReceipt -> ShowS)
-> (GetPaymentReceipt -> String)
-> ([GetPaymentReceipt] -> ShowS)
-> Show GetPaymentReceipt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPaymentReceipt] -> ShowS
$cshowList :: [GetPaymentReceipt] -> ShowS
show :: GetPaymentReceipt -> String
$cshow :: GetPaymentReceipt -> String
showsPrec :: Int -> GetPaymentReceipt -> ShowS
$cshowsPrec :: Int -> GetPaymentReceipt -> ShowS
Show, GetPaymentReceipt -> GetPaymentReceipt -> Bool
(GetPaymentReceipt -> GetPaymentReceipt -> Bool)
-> (GetPaymentReceipt -> GetPaymentReceipt -> Bool)
-> Eq GetPaymentReceipt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPaymentReceipt -> GetPaymentReceipt -> Bool
$c/= :: GetPaymentReceipt -> GetPaymentReceipt -> Bool
== :: GetPaymentReceipt -> GetPaymentReceipt -> Bool
$c== :: GetPaymentReceipt -> GetPaymentReceipt -> Bool
Eq, (forall x. GetPaymentReceipt -> Rep GetPaymentReceipt x)
-> (forall x. Rep GetPaymentReceipt x -> GetPaymentReceipt)
-> Generic GetPaymentReceipt
forall x. Rep GetPaymentReceipt x -> GetPaymentReceipt
forall x. GetPaymentReceipt -> Rep GetPaymentReceipt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPaymentReceipt x -> GetPaymentReceipt
$cfrom :: forall x. GetPaymentReceipt -> Rep GetPaymentReceipt x
Generic)

-- | Parameter of Function getSavedOrderInfo
data GetSavedOrderInfo
  = -- | Returns saved order info, if any
    GetSavedOrderInfo
      {
      }
  deriving (Int -> GetSavedOrderInfo -> ShowS
[GetSavedOrderInfo] -> ShowS
GetSavedOrderInfo -> String
(Int -> GetSavedOrderInfo -> ShowS)
-> (GetSavedOrderInfo -> String)
-> ([GetSavedOrderInfo] -> ShowS)
-> Show GetSavedOrderInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSavedOrderInfo] -> ShowS
$cshowList :: [GetSavedOrderInfo] -> ShowS
show :: GetSavedOrderInfo -> String
$cshow :: GetSavedOrderInfo -> String
showsPrec :: Int -> GetSavedOrderInfo -> ShowS
$cshowsPrec :: Int -> GetSavedOrderInfo -> ShowS
Show, GetSavedOrderInfo -> GetSavedOrderInfo -> Bool
(GetSavedOrderInfo -> GetSavedOrderInfo -> Bool)
-> (GetSavedOrderInfo -> GetSavedOrderInfo -> Bool)
-> Eq GetSavedOrderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSavedOrderInfo -> GetSavedOrderInfo -> Bool
$c/= :: GetSavedOrderInfo -> GetSavedOrderInfo -> Bool
== :: GetSavedOrderInfo -> GetSavedOrderInfo -> Bool
$c== :: GetSavedOrderInfo -> GetSavedOrderInfo -> Bool
Eq, (forall x. GetSavedOrderInfo -> Rep GetSavedOrderInfo x)
-> (forall x. Rep GetSavedOrderInfo x -> GetSavedOrderInfo)
-> Generic GetSavedOrderInfo
forall x. Rep GetSavedOrderInfo x -> GetSavedOrderInfo
forall x. GetSavedOrderInfo -> Rep GetSavedOrderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSavedOrderInfo x -> GetSavedOrderInfo
$cfrom :: forall x. GetSavedOrderInfo -> Rep GetSavedOrderInfo x
Generic)

-- | Parameter of Function deleteSavedOrderInfo
data DeleteSavedOrderInfo
  = -- | Deletes saved order info
    DeleteSavedOrderInfo
      {
      }
  deriving (Int -> DeleteSavedOrderInfo -> ShowS
[DeleteSavedOrderInfo] -> ShowS
DeleteSavedOrderInfo -> String
(Int -> DeleteSavedOrderInfo -> ShowS)
-> (DeleteSavedOrderInfo -> String)
-> ([DeleteSavedOrderInfo] -> ShowS)
-> Show DeleteSavedOrderInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSavedOrderInfo] -> ShowS
$cshowList :: [DeleteSavedOrderInfo] -> ShowS
show :: DeleteSavedOrderInfo -> String
$cshow :: DeleteSavedOrderInfo -> String
showsPrec :: Int -> DeleteSavedOrderInfo -> ShowS
$cshowsPrec :: Int -> DeleteSavedOrderInfo -> ShowS
Show, DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool
(DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool)
-> (DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool)
-> Eq DeleteSavedOrderInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool
$c/= :: DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool
== :: DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool
$c== :: DeleteSavedOrderInfo -> DeleteSavedOrderInfo -> Bool
Eq, (forall x. DeleteSavedOrderInfo -> Rep DeleteSavedOrderInfo x)
-> (forall x. Rep DeleteSavedOrderInfo x -> DeleteSavedOrderInfo)
-> Generic DeleteSavedOrderInfo
forall x. Rep DeleteSavedOrderInfo x -> DeleteSavedOrderInfo
forall x. DeleteSavedOrderInfo -> Rep DeleteSavedOrderInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSavedOrderInfo x -> DeleteSavedOrderInfo
$cfrom :: forall x. DeleteSavedOrderInfo -> Rep DeleteSavedOrderInfo x
Generic)

-- | Parameter of Function deleteSavedCredentials
data DeleteSavedCredentials
  = -- | Deletes saved credentials for all payment provider bots
    DeleteSavedCredentials
      {
      }
  deriving (Int -> DeleteSavedCredentials -> ShowS
[DeleteSavedCredentials] -> ShowS
DeleteSavedCredentials -> String
(Int -> DeleteSavedCredentials -> ShowS)
-> (DeleteSavedCredentials -> String)
-> ([DeleteSavedCredentials] -> ShowS)
-> Show DeleteSavedCredentials
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSavedCredentials] -> ShowS
$cshowList :: [DeleteSavedCredentials] -> ShowS
show :: DeleteSavedCredentials -> String
$cshow :: DeleteSavedCredentials -> String
showsPrec :: Int -> DeleteSavedCredentials -> ShowS
$cshowsPrec :: Int -> DeleteSavedCredentials -> ShowS
Show, DeleteSavedCredentials -> DeleteSavedCredentials -> Bool
(DeleteSavedCredentials -> DeleteSavedCredentials -> Bool)
-> (DeleteSavedCredentials -> DeleteSavedCredentials -> Bool)
-> Eq DeleteSavedCredentials
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSavedCredentials -> DeleteSavedCredentials -> Bool
$c/= :: DeleteSavedCredentials -> DeleteSavedCredentials -> Bool
== :: DeleteSavedCredentials -> DeleteSavedCredentials -> Bool
$c== :: DeleteSavedCredentials -> DeleteSavedCredentials -> Bool
Eq, (forall x. DeleteSavedCredentials -> Rep DeleteSavedCredentials x)
-> (forall x.
    Rep DeleteSavedCredentials x -> DeleteSavedCredentials)
-> Generic DeleteSavedCredentials
forall x. Rep DeleteSavedCredentials x -> DeleteSavedCredentials
forall x. DeleteSavedCredentials -> Rep DeleteSavedCredentials x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSavedCredentials x -> DeleteSavedCredentials
$cfrom :: forall x. DeleteSavedCredentials -> Rep DeleteSavedCredentials x
Generic)

-- | Parameter of Function getSupportUser
data GetSupportUser
  = -- | Returns a user that can be contacted to get support
    GetSupportUser
      {
      }
  deriving (Int -> GetSupportUser -> ShowS
[GetSupportUser] -> ShowS
GetSupportUser -> String
(Int -> GetSupportUser -> ShowS)
-> (GetSupportUser -> String)
-> ([GetSupportUser] -> ShowS)
-> Show GetSupportUser
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSupportUser] -> ShowS
$cshowList :: [GetSupportUser] -> ShowS
show :: GetSupportUser -> String
$cshow :: GetSupportUser -> String
showsPrec :: Int -> GetSupportUser -> ShowS
$cshowsPrec :: Int -> GetSupportUser -> ShowS
Show, GetSupportUser -> GetSupportUser -> Bool
(GetSupportUser -> GetSupportUser -> Bool)
-> (GetSupportUser -> GetSupportUser -> Bool) -> Eq GetSupportUser
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSupportUser -> GetSupportUser -> Bool
$c/= :: GetSupportUser -> GetSupportUser -> Bool
== :: GetSupportUser -> GetSupportUser -> Bool
$c== :: GetSupportUser -> GetSupportUser -> Bool
Eq, (forall x. GetSupportUser -> Rep GetSupportUser x)
-> (forall x. Rep GetSupportUser x -> GetSupportUser)
-> Generic GetSupportUser
forall x. Rep GetSupportUser x -> GetSupportUser
forall x. GetSupportUser -> Rep GetSupportUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSupportUser x -> GetSupportUser
$cfrom :: forall x. GetSupportUser -> Rep GetSupportUser x
Generic)

-- | Parameter of Function getBackgrounds
data GetBackgrounds
  = -- | Returns backgrounds installed by the user
    GetBackgrounds
      { -- | True, if the backgrounds needs to be ordered for dark theme
        GetBackgrounds -> Bool
for_dark_theme :: Bool
      }
  deriving (Int -> GetBackgrounds -> ShowS
[GetBackgrounds] -> ShowS
GetBackgrounds -> String
(Int -> GetBackgrounds -> ShowS)
-> (GetBackgrounds -> String)
-> ([GetBackgrounds] -> ShowS)
-> Show GetBackgrounds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackgrounds] -> ShowS
$cshowList :: [GetBackgrounds] -> ShowS
show :: GetBackgrounds -> String
$cshow :: GetBackgrounds -> String
showsPrec :: Int -> GetBackgrounds -> ShowS
$cshowsPrec :: Int -> GetBackgrounds -> ShowS
Show, GetBackgrounds -> GetBackgrounds -> Bool
(GetBackgrounds -> GetBackgrounds -> Bool)
-> (GetBackgrounds -> GetBackgrounds -> Bool) -> Eq GetBackgrounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackgrounds -> GetBackgrounds -> Bool
$c/= :: GetBackgrounds -> GetBackgrounds -> Bool
== :: GetBackgrounds -> GetBackgrounds -> Bool
$c== :: GetBackgrounds -> GetBackgrounds -> Bool
Eq, (forall x. GetBackgrounds -> Rep GetBackgrounds x)
-> (forall x. Rep GetBackgrounds x -> GetBackgrounds)
-> Generic GetBackgrounds
forall x. Rep GetBackgrounds x -> GetBackgrounds
forall x. GetBackgrounds -> Rep GetBackgrounds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBackgrounds x -> GetBackgrounds
$cfrom :: forall x. GetBackgrounds -> Rep GetBackgrounds x
Generic)

-- | Parameter of Function getBackgroundUrl
data GetBackgroundUrl
  = -- | Constructs a persistent HTTP URL for a background
    GetBackgroundUrl
      { -- | Background name
        GetBackgroundUrl -> T
name :: T,
        -- | Background type
        GetBackgroundUrl -> BackgroundType
type_ :: BackgroundType
      }
  deriving (Int -> GetBackgroundUrl -> ShowS
[GetBackgroundUrl] -> ShowS
GetBackgroundUrl -> String
(Int -> GetBackgroundUrl -> ShowS)
-> (GetBackgroundUrl -> String)
-> ([GetBackgroundUrl] -> ShowS)
-> Show GetBackgroundUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBackgroundUrl] -> ShowS
$cshowList :: [GetBackgroundUrl] -> ShowS
show :: GetBackgroundUrl -> String
$cshow :: GetBackgroundUrl -> String
showsPrec :: Int -> GetBackgroundUrl -> ShowS
$cshowsPrec :: Int -> GetBackgroundUrl -> ShowS
Show, GetBackgroundUrl -> GetBackgroundUrl -> Bool
(GetBackgroundUrl -> GetBackgroundUrl -> Bool)
-> (GetBackgroundUrl -> GetBackgroundUrl -> Bool)
-> Eq GetBackgroundUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBackgroundUrl -> GetBackgroundUrl -> Bool
$c/= :: GetBackgroundUrl -> GetBackgroundUrl -> Bool
== :: GetBackgroundUrl -> GetBackgroundUrl -> Bool
$c== :: GetBackgroundUrl -> GetBackgroundUrl -> Bool
Eq, (forall x. GetBackgroundUrl -> Rep GetBackgroundUrl x)
-> (forall x. Rep GetBackgroundUrl x -> GetBackgroundUrl)
-> Generic GetBackgroundUrl
forall x. Rep GetBackgroundUrl x -> GetBackgroundUrl
forall x. GetBackgroundUrl -> Rep GetBackgroundUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBackgroundUrl x -> GetBackgroundUrl
$cfrom :: forall x. GetBackgroundUrl -> Rep GetBackgroundUrl x
Generic)

-- | Parameter of Function searchBackground
data SearchBackground
  = -- | Searches for a background by its name
    SearchBackground
      { -- | The name of the background
        SearchBackground -> T
name :: T
      }
  deriving (Int -> SearchBackground -> ShowS
[SearchBackground] -> ShowS
SearchBackground -> String
(Int -> SearchBackground -> ShowS)
-> (SearchBackground -> String)
-> ([SearchBackground] -> ShowS)
-> Show SearchBackground
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchBackground] -> ShowS
$cshowList :: [SearchBackground] -> ShowS
show :: SearchBackground -> String
$cshow :: SearchBackground -> String
showsPrec :: Int -> SearchBackground -> ShowS
$cshowsPrec :: Int -> SearchBackground -> ShowS
Show, SearchBackground -> SearchBackground -> Bool
(SearchBackground -> SearchBackground -> Bool)
-> (SearchBackground -> SearchBackground -> Bool)
-> Eq SearchBackground
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchBackground -> SearchBackground -> Bool
$c/= :: SearchBackground -> SearchBackground -> Bool
== :: SearchBackground -> SearchBackground -> Bool
$c== :: SearchBackground -> SearchBackground -> Bool
Eq, (forall x. SearchBackground -> Rep SearchBackground x)
-> (forall x. Rep SearchBackground x -> SearchBackground)
-> Generic SearchBackground
forall x. Rep SearchBackground x -> SearchBackground
forall x. SearchBackground -> Rep SearchBackground x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchBackground x -> SearchBackground
$cfrom :: forall x. SearchBackground -> Rep SearchBackground x
Generic)

-- | Parameter of Function setBackground
data SetBackground
  = -- | Changes the background selected by the user; adds background to the list of installed backgrounds
    SetBackground
      { -- | The input background to use, null for filled backgrounds
        SetBackground -> InputBackground
background :: InputBackground,
        -- | Background type; null for default background. The method will return error 404 if type is null
        SetBackground -> BackgroundType
type_ :: BackgroundType,
        -- | True, if the background is chosen for dark theme
        SetBackground -> Bool
for_dark_theme :: Bool
      }
  deriving (Int -> SetBackground -> ShowS
[SetBackground] -> ShowS
SetBackground -> String
(Int -> SetBackground -> ShowS)
-> (SetBackground -> String)
-> ([SetBackground] -> ShowS)
-> Show SetBackground
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetBackground] -> ShowS
$cshowList :: [SetBackground] -> ShowS
show :: SetBackground -> String
$cshow :: SetBackground -> String
showsPrec :: Int -> SetBackground -> ShowS
$cshowsPrec :: Int -> SetBackground -> ShowS
Show, SetBackground -> SetBackground -> Bool
(SetBackground -> SetBackground -> Bool)
-> (SetBackground -> SetBackground -> Bool) -> Eq SetBackground
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetBackground -> SetBackground -> Bool
$c/= :: SetBackground -> SetBackground -> Bool
== :: SetBackground -> SetBackground -> Bool
$c== :: SetBackground -> SetBackground -> Bool
Eq, (forall x. SetBackground -> Rep SetBackground x)
-> (forall x. Rep SetBackground x -> SetBackground)
-> Generic SetBackground
forall x. Rep SetBackground x -> SetBackground
forall x. SetBackground -> Rep SetBackground x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetBackground x -> SetBackground
$cfrom :: forall x. SetBackground -> Rep SetBackground x
Generic)

-- | Parameter of Function removeBackground
data RemoveBackground
  = -- | Removes background from the list of installed backgrounds
    RemoveBackground
      { -- | The background identifier
        RemoveBackground -> I64
background_id :: I64
      }
  deriving (Int -> RemoveBackground -> ShowS
[RemoveBackground] -> ShowS
RemoveBackground -> String
(Int -> RemoveBackground -> ShowS)
-> (RemoveBackground -> String)
-> ([RemoveBackground] -> ShowS)
-> Show RemoveBackground
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveBackground] -> ShowS
$cshowList :: [RemoveBackground] -> ShowS
show :: RemoveBackground -> String
$cshow :: RemoveBackground -> String
showsPrec :: Int -> RemoveBackground -> ShowS
$cshowsPrec :: Int -> RemoveBackground -> ShowS
Show, RemoveBackground -> RemoveBackground -> Bool
(RemoveBackground -> RemoveBackground -> Bool)
-> (RemoveBackground -> RemoveBackground -> Bool)
-> Eq RemoveBackground
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveBackground -> RemoveBackground -> Bool
$c/= :: RemoveBackground -> RemoveBackground -> Bool
== :: RemoveBackground -> RemoveBackground -> Bool
$c== :: RemoveBackground -> RemoveBackground -> Bool
Eq, (forall x. RemoveBackground -> Rep RemoveBackground x)
-> (forall x. Rep RemoveBackground x -> RemoveBackground)
-> Generic RemoveBackground
forall x. Rep RemoveBackground x -> RemoveBackground
forall x. RemoveBackground -> Rep RemoveBackground x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveBackground x -> RemoveBackground
$cfrom :: forall x. RemoveBackground -> Rep RemoveBackground x
Generic)

-- | Parameter of Function resetBackgrounds
data ResetBackgrounds
  = -- | Resets list of installed backgrounds to its default value
    ResetBackgrounds
      {
      }
  deriving (Int -> ResetBackgrounds -> ShowS
[ResetBackgrounds] -> ShowS
ResetBackgrounds -> String
(Int -> ResetBackgrounds -> ShowS)
-> (ResetBackgrounds -> String)
-> ([ResetBackgrounds] -> ShowS)
-> Show ResetBackgrounds
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetBackgrounds] -> ShowS
$cshowList :: [ResetBackgrounds] -> ShowS
show :: ResetBackgrounds -> String
$cshow :: ResetBackgrounds -> String
showsPrec :: Int -> ResetBackgrounds -> ShowS
$cshowsPrec :: Int -> ResetBackgrounds -> ShowS
Show, ResetBackgrounds -> ResetBackgrounds -> Bool
(ResetBackgrounds -> ResetBackgrounds -> Bool)
-> (ResetBackgrounds -> ResetBackgrounds -> Bool)
-> Eq ResetBackgrounds
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetBackgrounds -> ResetBackgrounds -> Bool
$c/= :: ResetBackgrounds -> ResetBackgrounds -> Bool
== :: ResetBackgrounds -> ResetBackgrounds -> Bool
$c== :: ResetBackgrounds -> ResetBackgrounds -> Bool
Eq, (forall x. ResetBackgrounds -> Rep ResetBackgrounds x)
-> (forall x. Rep ResetBackgrounds x -> ResetBackgrounds)
-> Generic ResetBackgrounds
forall x. Rep ResetBackgrounds x -> ResetBackgrounds
forall x. ResetBackgrounds -> Rep ResetBackgrounds x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetBackgrounds x -> ResetBackgrounds
$cfrom :: forall x. ResetBackgrounds -> Rep ResetBackgrounds x
Generic)

-- | Parameter of Function getLocalizationTargetInfo
data GetLocalizationTargetInfo
  = -- | Returns information about the current localization target. This is an offline request if only_local is true. Can be called before authorization
    GetLocalizationTargetInfo
      { -- | If true, returns only locally available information without sending network requests
        GetLocalizationTargetInfo -> Bool
only_local :: Bool
      }
  deriving (Int -> GetLocalizationTargetInfo -> ShowS
[GetLocalizationTargetInfo] -> ShowS
GetLocalizationTargetInfo -> String
(Int -> GetLocalizationTargetInfo -> ShowS)
-> (GetLocalizationTargetInfo -> String)
-> ([GetLocalizationTargetInfo] -> ShowS)
-> Show GetLocalizationTargetInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLocalizationTargetInfo] -> ShowS
$cshowList :: [GetLocalizationTargetInfo] -> ShowS
show :: GetLocalizationTargetInfo -> String
$cshow :: GetLocalizationTargetInfo -> String
showsPrec :: Int -> GetLocalizationTargetInfo -> ShowS
$cshowsPrec :: Int -> GetLocalizationTargetInfo -> ShowS
Show, GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool
(GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool)
-> (GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool)
-> Eq GetLocalizationTargetInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool
$c/= :: GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool
== :: GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool
$c== :: GetLocalizationTargetInfo -> GetLocalizationTargetInfo -> Bool
Eq, (forall x.
 GetLocalizationTargetInfo -> Rep GetLocalizationTargetInfo x)
-> (forall x.
    Rep GetLocalizationTargetInfo x -> GetLocalizationTargetInfo)
-> Generic GetLocalizationTargetInfo
forall x.
Rep GetLocalizationTargetInfo x -> GetLocalizationTargetInfo
forall x.
GetLocalizationTargetInfo -> Rep GetLocalizationTargetInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetLocalizationTargetInfo x -> GetLocalizationTargetInfo
$cfrom :: forall x.
GetLocalizationTargetInfo -> Rep GetLocalizationTargetInfo x
Generic)

-- | Parameter of Function getLanguagePackInfo
data GetLanguagePackInfo
  = -- | Returns information about a language pack. Returned language pack identifier may be different from a provided one. Can be called before authorization
    GetLanguagePackInfo
      { -- | Language pack identifier
        GetLanguagePackInfo -> T
language_pack_id :: T
      }
  deriving (Int -> GetLanguagePackInfo -> ShowS
[GetLanguagePackInfo] -> ShowS
GetLanguagePackInfo -> String
(Int -> GetLanguagePackInfo -> ShowS)
-> (GetLanguagePackInfo -> String)
-> ([GetLanguagePackInfo] -> ShowS)
-> Show GetLanguagePackInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLanguagePackInfo] -> ShowS
$cshowList :: [GetLanguagePackInfo] -> ShowS
show :: GetLanguagePackInfo -> String
$cshow :: GetLanguagePackInfo -> String
showsPrec :: Int -> GetLanguagePackInfo -> ShowS
$cshowsPrec :: Int -> GetLanguagePackInfo -> ShowS
Show, GetLanguagePackInfo -> GetLanguagePackInfo -> Bool
(GetLanguagePackInfo -> GetLanguagePackInfo -> Bool)
-> (GetLanguagePackInfo -> GetLanguagePackInfo -> Bool)
-> Eq GetLanguagePackInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLanguagePackInfo -> GetLanguagePackInfo -> Bool
$c/= :: GetLanguagePackInfo -> GetLanguagePackInfo -> Bool
== :: GetLanguagePackInfo -> GetLanguagePackInfo -> Bool
$c== :: GetLanguagePackInfo -> GetLanguagePackInfo -> Bool
Eq, (forall x. GetLanguagePackInfo -> Rep GetLanguagePackInfo x)
-> (forall x. Rep GetLanguagePackInfo x -> GetLanguagePackInfo)
-> Generic GetLanguagePackInfo
forall x. Rep GetLanguagePackInfo x -> GetLanguagePackInfo
forall x. GetLanguagePackInfo -> Rep GetLanguagePackInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLanguagePackInfo x -> GetLanguagePackInfo
$cfrom :: forall x. GetLanguagePackInfo -> Rep GetLanguagePackInfo x
Generic)

-- | Parameter of Function getLanguagePackStrings
data GetLanguagePackStrings
  = -- | Returns strings from a language pack in the current localization target by their keys. Can be called before authorization
    GetLanguagePackStrings
      { -- | Language pack identifier of the strings to be returned
        GetLanguagePackStrings -> T
language_pack_id :: T,
        -- | Language pack keys of the strings to be returned; leave empty to request all available strings
        GetLanguagePackStrings -> [T]
keys :: ([]) (T)
      }
  deriving (Int -> GetLanguagePackStrings -> ShowS
[GetLanguagePackStrings] -> ShowS
GetLanguagePackStrings -> String
(Int -> GetLanguagePackStrings -> ShowS)
-> (GetLanguagePackStrings -> String)
-> ([GetLanguagePackStrings] -> ShowS)
-> Show GetLanguagePackStrings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLanguagePackStrings] -> ShowS
$cshowList :: [GetLanguagePackStrings] -> ShowS
show :: GetLanguagePackStrings -> String
$cshow :: GetLanguagePackStrings -> String
showsPrec :: Int -> GetLanguagePackStrings -> ShowS
$cshowsPrec :: Int -> GetLanguagePackStrings -> ShowS
Show, GetLanguagePackStrings -> GetLanguagePackStrings -> Bool
(GetLanguagePackStrings -> GetLanguagePackStrings -> Bool)
-> (GetLanguagePackStrings -> GetLanguagePackStrings -> Bool)
-> Eq GetLanguagePackStrings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLanguagePackStrings -> GetLanguagePackStrings -> Bool
$c/= :: GetLanguagePackStrings -> GetLanguagePackStrings -> Bool
== :: GetLanguagePackStrings -> GetLanguagePackStrings -> Bool
$c== :: GetLanguagePackStrings -> GetLanguagePackStrings -> Bool
Eq, (forall x. GetLanguagePackStrings -> Rep GetLanguagePackStrings x)
-> (forall x.
    Rep GetLanguagePackStrings x -> GetLanguagePackStrings)
-> Generic GetLanguagePackStrings
forall x. Rep GetLanguagePackStrings x -> GetLanguagePackStrings
forall x. GetLanguagePackStrings -> Rep GetLanguagePackStrings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLanguagePackStrings x -> GetLanguagePackStrings
$cfrom :: forall x. GetLanguagePackStrings -> Rep GetLanguagePackStrings x
Generic)

-- | Parameter of Function synchronizeLanguagePack
data SynchronizeLanguagePack
  = -- | Fetches the latest versions of all strings from a language pack in the current localization target from the server. This method doesn't need to be called explicitly for the current used/base language packs. Can be called before authorization
    SynchronizeLanguagePack
      { -- | Language pack identifier
        SynchronizeLanguagePack -> T
language_pack_id :: T
      }
  deriving (Int -> SynchronizeLanguagePack -> ShowS
[SynchronizeLanguagePack] -> ShowS
SynchronizeLanguagePack -> String
(Int -> SynchronizeLanguagePack -> ShowS)
-> (SynchronizeLanguagePack -> String)
-> ([SynchronizeLanguagePack] -> ShowS)
-> Show SynchronizeLanguagePack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SynchronizeLanguagePack] -> ShowS
$cshowList :: [SynchronizeLanguagePack] -> ShowS
show :: SynchronizeLanguagePack -> String
$cshow :: SynchronizeLanguagePack -> String
showsPrec :: Int -> SynchronizeLanguagePack -> ShowS
$cshowsPrec :: Int -> SynchronizeLanguagePack -> ShowS
Show, SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool
(SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool)
-> (SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool)
-> Eq SynchronizeLanguagePack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool
$c/= :: SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool
== :: SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool
$c== :: SynchronizeLanguagePack -> SynchronizeLanguagePack -> Bool
Eq, (forall x.
 SynchronizeLanguagePack -> Rep SynchronizeLanguagePack x)
-> (forall x.
    Rep SynchronizeLanguagePack x -> SynchronizeLanguagePack)
-> Generic SynchronizeLanguagePack
forall x. Rep SynchronizeLanguagePack x -> SynchronizeLanguagePack
forall x. SynchronizeLanguagePack -> Rep SynchronizeLanguagePack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SynchronizeLanguagePack x -> SynchronizeLanguagePack
$cfrom :: forall x. SynchronizeLanguagePack -> Rep SynchronizeLanguagePack x
Generic)

-- | Parameter of Function addCustomServerLanguagePack
data AddCustomServerLanguagePack
  = -- | Adds a custom server language pack to the list of installed language packs in current localization target. Can be called before authorization
    AddCustomServerLanguagePack
      { -- | Identifier of a language pack to be added; may be different from a name that is used in an "https://t.me/setlanguage/" link
        AddCustomServerLanguagePack -> T
language_pack_id :: T
      }
  deriving (Int -> AddCustomServerLanguagePack -> ShowS
[AddCustomServerLanguagePack] -> ShowS
AddCustomServerLanguagePack -> String
(Int -> AddCustomServerLanguagePack -> ShowS)
-> (AddCustomServerLanguagePack -> String)
-> ([AddCustomServerLanguagePack] -> ShowS)
-> Show AddCustomServerLanguagePack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddCustomServerLanguagePack] -> ShowS
$cshowList :: [AddCustomServerLanguagePack] -> ShowS
show :: AddCustomServerLanguagePack -> String
$cshow :: AddCustomServerLanguagePack -> String
showsPrec :: Int -> AddCustomServerLanguagePack -> ShowS
$cshowsPrec :: Int -> AddCustomServerLanguagePack -> ShowS
Show, AddCustomServerLanguagePack -> AddCustomServerLanguagePack -> Bool
(AddCustomServerLanguagePack
 -> AddCustomServerLanguagePack -> Bool)
-> (AddCustomServerLanguagePack
    -> AddCustomServerLanguagePack -> Bool)
-> Eq AddCustomServerLanguagePack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddCustomServerLanguagePack -> AddCustomServerLanguagePack -> Bool
$c/= :: AddCustomServerLanguagePack -> AddCustomServerLanguagePack -> Bool
== :: AddCustomServerLanguagePack -> AddCustomServerLanguagePack -> Bool
$c== :: AddCustomServerLanguagePack -> AddCustomServerLanguagePack -> Bool
Eq, (forall x.
 AddCustomServerLanguagePack -> Rep AddCustomServerLanguagePack x)
-> (forall x.
    Rep AddCustomServerLanguagePack x -> AddCustomServerLanguagePack)
-> Generic AddCustomServerLanguagePack
forall x.
Rep AddCustomServerLanguagePack x -> AddCustomServerLanguagePack
forall x.
AddCustomServerLanguagePack -> Rep AddCustomServerLanguagePack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddCustomServerLanguagePack x -> AddCustomServerLanguagePack
$cfrom :: forall x.
AddCustomServerLanguagePack -> Rep AddCustomServerLanguagePack x
Generic)

-- | Parameter of Function setCustomLanguagePack
data SetCustomLanguagePack
  = -- | Adds or changes a custom local language pack to the current localization target
    SetCustomLanguagePack
      { -- | Information about the language pack. Language pack ID must start with 'X', consist only of English letters, digits and hyphens, and must not exceed 64 characters. Can be called before authorization
        SetCustomLanguagePack -> LanguagePackInfo
info :: LanguagePackInfo,
        -- | Strings of the new language pack
        SetCustomLanguagePack -> [LanguagePackString]
strings :: ([]) (LanguagePackString)
      }
  deriving (Int -> SetCustomLanguagePack -> ShowS
[SetCustomLanguagePack] -> ShowS
SetCustomLanguagePack -> String
(Int -> SetCustomLanguagePack -> ShowS)
-> (SetCustomLanguagePack -> String)
-> ([SetCustomLanguagePack] -> ShowS)
-> Show SetCustomLanguagePack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetCustomLanguagePack] -> ShowS
$cshowList :: [SetCustomLanguagePack] -> ShowS
show :: SetCustomLanguagePack -> String
$cshow :: SetCustomLanguagePack -> String
showsPrec :: Int -> SetCustomLanguagePack -> ShowS
$cshowsPrec :: Int -> SetCustomLanguagePack -> ShowS
Show, SetCustomLanguagePack -> SetCustomLanguagePack -> Bool
(SetCustomLanguagePack -> SetCustomLanguagePack -> Bool)
-> (SetCustomLanguagePack -> SetCustomLanguagePack -> Bool)
-> Eq SetCustomLanguagePack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetCustomLanguagePack -> SetCustomLanguagePack -> Bool
$c/= :: SetCustomLanguagePack -> SetCustomLanguagePack -> Bool
== :: SetCustomLanguagePack -> SetCustomLanguagePack -> Bool
$c== :: SetCustomLanguagePack -> SetCustomLanguagePack -> Bool
Eq, (forall x. SetCustomLanguagePack -> Rep SetCustomLanguagePack x)
-> (forall x. Rep SetCustomLanguagePack x -> SetCustomLanguagePack)
-> Generic SetCustomLanguagePack
forall x. Rep SetCustomLanguagePack x -> SetCustomLanguagePack
forall x. SetCustomLanguagePack -> Rep SetCustomLanguagePack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetCustomLanguagePack x -> SetCustomLanguagePack
$cfrom :: forall x. SetCustomLanguagePack -> Rep SetCustomLanguagePack x
Generic)

-- | Parameter of Function editCustomLanguagePackInfo
data EditCustomLanguagePackInfo
  = -- | Edits information about a custom local language pack in the current localization target. Can be called before authorization
    EditCustomLanguagePackInfo
      { -- | New information about the custom local language pack
        EditCustomLanguagePackInfo -> LanguagePackInfo
info :: LanguagePackInfo
      }
  deriving (Int -> EditCustomLanguagePackInfo -> ShowS
[EditCustomLanguagePackInfo] -> ShowS
EditCustomLanguagePackInfo -> String
(Int -> EditCustomLanguagePackInfo -> ShowS)
-> (EditCustomLanguagePackInfo -> String)
-> ([EditCustomLanguagePackInfo] -> ShowS)
-> Show EditCustomLanguagePackInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditCustomLanguagePackInfo] -> ShowS
$cshowList :: [EditCustomLanguagePackInfo] -> ShowS
show :: EditCustomLanguagePackInfo -> String
$cshow :: EditCustomLanguagePackInfo -> String
showsPrec :: Int -> EditCustomLanguagePackInfo -> ShowS
$cshowsPrec :: Int -> EditCustomLanguagePackInfo -> ShowS
Show, EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool
(EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool)
-> (EditCustomLanguagePackInfo
    -> EditCustomLanguagePackInfo -> Bool)
-> Eq EditCustomLanguagePackInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool
$c/= :: EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool
== :: EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool
$c== :: EditCustomLanguagePackInfo -> EditCustomLanguagePackInfo -> Bool
Eq, (forall x.
 EditCustomLanguagePackInfo -> Rep EditCustomLanguagePackInfo x)
-> (forall x.
    Rep EditCustomLanguagePackInfo x -> EditCustomLanguagePackInfo)
-> Generic EditCustomLanguagePackInfo
forall x.
Rep EditCustomLanguagePackInfo x -> EditCustomLanguagePackInfo
forall x.
EditCustomLanguagePackInfo -> Rep EditCustomLanguagePackInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep EditCustomLanguagePackInfo x -> EditCustomLanguagePackInfo
$cfrom :: forall x.
EditCustomLanguagePackInfo -> Rep EditCustomLanguagePackInfo x
Generic)

-- | Parameter of Function setCustomLanguagePackString
data SetCustomLanguagePackString
  = -- | Adds, edits or deletes a string in a custom local language pack. Can be called before authorization
    SetCustomLanguagePackString
      { -- | Identifier of a previously added custom local language pack in the current localization target
        SetCustomLanguagePackString -> T
language_pack_id :: T,
        -- | New language pack string
        SetCustomLanguagePackString -> LanguagePackString
new_string :: LanguagePackString
      }
  deriving (Int -> SetCustomLanguagePackString -> ShowS
[SetCustomLanguagePackString] -> ShowS
SetCustomLanguagePackString -> String
(Int -> SetCustomLanguagePackString -> ShowS)
-> (SetCustomLanguagePackString -> String)
-> ([SetCustomLanguagePackString] -> ShowS)
-> Show SetCustomLanguagePackString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetCustomLanguagePackString] -> ShowS
$cshowList :: [SetCustomLanguagePackString] -> ShowS
show :: SetCustomLanguagePackString -> String
$cshow :: SetCustomLanguagePackString -> String
showsPrec :: Int -> SetCustomLanguagePackString -> ShowS
$cshowsPrec :: Int -> SetCustomLanguagePackString -> ShowS
Show, SetCustomLanguagePackString -> SetCustomLanguagePackString -> Bool
(SetCustomLanguagePackString
 -> SetCustomLanguagePackString -> Bool)
-> (SetCustomLanguagePackString
    -> SetCustomLanguagePackString -> Bool)
-> Eq SetCustomLanguagePackString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetCustomLanguagePackString -> SetCustomLanguagePackString -> Bool
$c/= :: SetCustomLanguagePackString -> SetCustomLanguagePackString -> Bool
== :: SetCustomLanguagePackString -> SetCustomLanguagePackString -> Bool
$c== :: SetCustomLanguagePackString -> SetCustomLanguagePackString -> Bool
Eq, (forall x.
 SetCustomLanguagePackString -> Rep SetCustomLanguagePackString x)
-> (forall x.
    Rep SetCustomLanguagePackString x -> SetCustomLanguagePackString)
-> Generic SetCustomLanguagePackString
forall x.
Rep SetCustomLanguagePackString x -> SetCustomLanguagePackString
forall x.
SetCustomLanguagePackString -> Rep SetCustomLanguagePackString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetCustomLanguagePackString x -> SetCustomLanguagePackString
$cfrom :: forall x.
SetCustomLanguagePackString -> Rep SetCustomLanguagePackString x
Generic)

-- | Parameter of Function deleteLanguagePack
data DeleteLanguagePack
  = -- | Deletes all information about a language pack in the current localization target. The language pack which is currently in use (including base language pack) or is being synchronized can't be deleted. Can be called before authorization
    DeleteLanguagePack
      { -- | Identifier of the language pack to delete
        DeleteLanguagePack -> T
language_pack_id :: T
      }
  deriving (Int -> DeleteLanguagePack -> ShowS
[DeleteLanguagePack] -> ShowS
DeleteLanguagePack -> String
(Int -> DeleteLanguagePack -> ShowS)
-> (DeleteLanguagePack -> String)
-> ([DeleteLanguagePack] -> ShowS)
-> Show DeleteLanguagePack
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLanguagePack] -> ShowS
$cshowList :: [DeleteLanguagePack] -> ShowS
show :: DeleteLanguagePack -> String
$cshow :: DeleteLanguagePack -> String
showsPrec :: Int -> DeleteLanguagePack -> ShowS
$cshowsPrec :: Int -> DeleteLanguagePack -> ShowS
Show, DeleteLanguagePack -> DeleteLanguagePack -> Bool
(DeleteLanguagePack -> DeleteLanguagePack -> Bool)
-> (DeleteLanguagePack -> DeleteLanguagePack -> Bool)
-> Eq DeleteLanguagePack
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLanguagePack -> DeleteLanguagePack -> Bool
$c/= :: DeleteLanguagePack -> DeleteLanguagePack -> Bool
== :: DeleteLanguagePack -> DeleteLanguagePack -> Bool
$c== :: DeleteLanguagePack -> DeleteLanguagePack -> Bool
Eq, (forall x. DeleteLanguagePack -> Rep DeleteLanguagePack x)
-> (forall x. Rep DeleteLanguagePack x -> DeleteLanguagePack)
-> Generic DeleteLanguagePack
forall x. Rep DeleteLanguagePack x -> DeleteLanguagePack
forall x. DeleteLanguagePack -> Rep DeleteLanguagePack x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLanguagePack x -> DeleteLanguagePack
$cfrom :: forall x. DeleteLanguagePack -> Rep DeleteLanguagePack x
Generic)

-- | Parameter of Function registerDevice
data RegisterDevice
  = -- | Registers the currently used device for receiving push notifications. Returns a globally unique identifier of the push notification subscription
    RegisterDevice
      { -- | Device token
        RegisterDevice -> DeviceToken
device_token :: DeviceToken,
        -- | List of user identifiers of other users currently using the client
        RegisterDevice -> [Int]
other_user_ids :: ([]) (I32)
      }
  deriving (Int -> RegisterDevice -> ShowS
[RegisterDevice] -> ShowS
RegisterDevice -> String
(Int -> RegisterDevice -> ShowS)
-> (RegisterDevice -> String)
-> ([RegisterDevice] -> ShowS)
-> Show RegisterDevice
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RegisterDevice] -> ShowS
$cshowList :: [RegisterDevice] -> ShowS
show :: RegisterDevice -> String
$cshow :: RegisterDevice -> String
showsPrec :: Int -> RegisterDevice -> ShowS
$cshowsPrec :: Int -> RegisterDevice -> ShowS
Show, RegisterDevice -> RegisterDevice -> Bool
(RegisterDevice -> RegisterDevice -> Bool)
-> (RegisterDevice -> RegisterDevice -> Bool) -> Eq RegisterDevice
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RegisterDevice -> RegisterDevice -> Bool
$c/= :: RegisterDevice -> RegisterDevice -> Bool
== :: RegisterDevice -> RegisterDevice -> Bool
$c== :: RegisterDevice -> RegisterDevice -> Bool
Eq, (forall x. RegisterDevice -> Rep RegisterDevice x)
-> (forall x. Rep RegisterDevice x -> RegisterDevice)
-> Generic RegisterDevice
forall x. Rep RegisterDevice x -> RegisterDevice
forall x. RegisterDevice -> Rep RegisterDevice x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterDevice x -> RegisterDevice
$cfrom :: forall x. RegisterDevice -> Rep RegisterDevice x
Generic)

-- | Parameter of Function processPushNotification
data ProcessPushNotification
  = -- | Handles a push notification. Returns error with code 406 if the push notification is not supported and connection to the server is required to fetch new data. Can be called before authorization
    ProcessPushNotification
      { -- | JSON-encoded push notification payload with all fields sent by the server, and "google.sent_time" and "google.notification.sound" fields added
        ProcessPushNotification -> T
payload :: T
      }
  deriving (Int -> ProcessPushNotification -> ShowS
[ProcessPushNotification] -> ShowS
ProcessPushNotification -> String
(Int -> ProcessPushNotification -> ShowS)
-> (ProcessPushNotification -> String)
-> ([ProcessPushNotification] -> ShowS)
-> Show ProcessPushNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessPushNotification] -> ShowS
$cshowList :: [ProcessPushNotification] -> ShowS
show :: ProcessPushNotification -> String
$cshow :: ProcessPushNotification -> String
showsPrec :: Int -> ProcessPushNotification -> ShowS
$cshowsPrec :: Int -> ProcessPushNotification -> ShowS
Show, ProcessPushNotification -> ProcessPushNotification -> Bool
(ProcessPushNotification -> ProcessPushNotification -> Bool)
-> (ProcessPushNotification -> ProcessPushNotification -> Bool)
-> Eq ProcessPushNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessPushNotification -> ProcessPushNotification -> Bool
$c/= :: ProcessPushNotification -> ProcessPushNotification -> Bool
== :: ProcessPushNotification -> ProcessPushNotification -> Bool
$c== :: ProcessPushNotification -> ProcessPushNotification -> Bool
Eq, (forall x.
 ProcessPushNotification -> Rep ProcessPushNotification x)
-> (forall x.
    Rep ProcessPushNotification x -> ProcessPushNotification)
-> Generic ProcessPushNotification
forall x. Rep ProcessPushNotification x -> ProcessPushNotification
forall x. ProcessPushNotification -> Rep ProcessPushNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProcessPushNotification x -> ProcessPushNotification
$cfrom :: forall x. ProcessPushNotification -> Rep ProcessPushNotification x
Generic)

-- | Parameter of Function getPushReceiverId
data GetPushReceiverId
  = -- | Returns a globally unique push notification subscription identifier for identification of an account, which has received a push notification. This is an offline method. Can be called before authorization. Can be called synchronously
    GetPushReceiverId
      { -- | JSON-encoded push notification payload
        GetPushReceiverId -> T
payload :: T
      }
  deriving (Int -> GetPushReceiverId -> ShowS
[GetPushReceiverId] -> ShowS
GetPushReceiverId -> String
(Int -> GetPushReceiverId -> ShowS)
-> (GetPushReceiverId -> String)
-> ([GetPushReceiverId] -> ShowS)
-> Show GetPushReceiverId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPushReceiverId] -> ShowS
$cshowList :: [GetPushReceiverId] -> ShowS
show :: GetPushReceiverId -> String
$cshow :: GetPushReceiverId -> String
showsPrec :: Int -> GetPushReceiverId -> ShowS
$cshowsPrec :: Int -> GetPushReceiverId -> ShowS
Show, GetPushReceiverId -> GetPushReceiverId -> Bool
(GetPushReceiverId -> GetPushReceiverId -> Bool)
-> (GetPushReceiverId -> GetPushReceiverId -> Bool)
-> Eq GetPushReceiverId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPushReceiverId -> GetPushReceiverId -> Bool
$c/= :: GetPushReceiverId -> GetPushReceiverId -> Bool
== :: GetPushReceiverId -> GetPushReceiverId -> Bool
$c== :: GetPushReceiverId -> GetPushReceiverId -> Bool
Eq, (forall x. GetPushReceiverId -> Rep GetPushReceiverId x)
-> (forall x. Rep GetPushReceiverId x -> GetPushReceiverId)
-> Generic GetPushReceiverId
forall x. Rep GetPushReceiverId x -> GetPushReceiverId
forall x. GetPushReceiverId -> Rep GetPushReceiverId x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPushReceiverId x -> GetPushReceiverId
$cfrom :: forall x. GetPushReceiverId -> Rep GetPushReceiverId x
Generic)

-- | Parameter of Function getRecentlyVisitedTMeUrls
data GetRecentlyVisitedTMeUrls
  = -- | Returns t.me URLs recently visited by a newly registered user
    GetRecentlyVisitedTMeUrls
      { -- | Google Play referrer to identify the user
        GetRecentlyVisitedTMeUrls -> T
referrer :: T
      }
  deriving (Int -> GetRecentlyVisitedTMeUrls -> ShowS
[GetRecentlyVisitedTMeUrls] -> ShowS
GetRecentlyVisitedTMeUrls -> String
(Int -> GetRecentlyVisitedTMeUrls -> ShowS)
-> (GetRecentlyVisitedTMeUrls -> String)
-> ([GetRecentlyVisitedTMeUrls] -> ShowS)
-> Show GetRecentlyVisitedTMeUrls
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetRecentlyVisitedTMeUrls] -> ShowS
$cshowList :: [GetRecentlyVisitedTMeUrls] -> ShowS
show :: GetRecentlyVisitedTMeUrls -> String
$cshow :: GetRecentlyVisitedTMeUrls -> String
showsPrec :: Int -> GetRecentlyVisitedTMeUrls -> ShowS
$cshowsPrec :: Int -> GetRecentlyVisitedTMeUrls -> ShowS
Show, GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool
(GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool)
-> (GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool)
-> Eq GetRecentlyVisitedTMeUrls
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool
$c/= :: GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool
== :: GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool
$c== :: GetRecentlyVisitedTMeUrls -> GetRecentlyVisitedTMeUrls -> Bool
Eq, (forall x.
 GetRecentlyVisitedTMeUrls -> Rep GetRecentlyVisitedTMeUrls x)
-> (forall x.
    Rep GetRecentlyVisitedTMeUrls x -> GetRecentlyVisitedTMeUrls)
-> Generic GetRecentlyVisitedTMeUrls
forall x.
Rep GetRecentlyVisitedTMeUrls x -> GetRecentlyVisitedTMeUrls
forall x.
GetRecentlyVisitedTMeUrls -> Rep GetRecentlyVisitedTMeUrls x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetRecentlyVisitedTMeUrls x -> GetRecentlyVisitedTMeUrls
$cfrom :: forall x.
GetRecentlyVisitedTMeUrls -> Rep GetRecentlyVisitedTMeUrls x
Generic)

-- | Parameter of Function setUserPrivacySettingRules
data SetUserPrivacySettingRules
  = -- | Changes user privacy settings
    SetUserPrivacySettingRules
      { -- | The privacy setting
        SetUserPrivacySettingRules -> UserPrivacySetting
setting :: UserPrivacySetting,
        -- | The new privacy rules
        SetUserPrivacySettingRules -> UserPrivacySettingRules
rules :: UserPrivacySettingRules
      }
  deriving (Int -> SetUserPrivacySettingRules -> ShowS
[SetUserPrivacySettingRules] -> ShowS
SetUserPrivacySettingRules -> String
(Int -> SetUserPrivacySettingRules -> ShowS)
-> (SetUserPrivacySettingRules -> String)
-> ([SetUserPrivacySettingRules] -> ShowS)
-> Show SetUserPrivacySettingRules
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetUserPrivacySettingRules] -> ShowS
$cshowList :: [SetUserPrivacySettingRules] -> ShowS
show :: SetUserPrivacySettingRules -> String
$cshow :: SetUserPrivacySettingRules -> String
showsPrec :: Int -> SetUserPrivacySettingRules -> ShowS
$cshowsPrec :: Int -> SetUserPrivacySettingRules -> ShowS
Show, SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool
(SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool)
-> (SetUserPrivacySettingRules
    -> SetUserPrivacySettingRules -> Bool)
-> Eq SetUserPrivacySettingRules
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool
$c/= :: SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool
== :: SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool
$c== :: SetUserPrivacySettingRules -> SetUserPrivacySettingRules -> Bool
Eq, (forall x.
 SetUserPrivacySettingRules -> Rep SetUserPrivacySettingRules x)
-> (forall x.
    Rep SetUserPrivacySettingRules x -> SetUserPrivacySettingRules)
-> Generic SetUserPrivacySettingRules
forall x.
Rep SetUserPrivacySettingRules x -> SetUserPrivacySettingRules
forall x.
SetUserPrivacySettingRules -> Rep SetUserPrivacySettingRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetUserPrivacySettingRules x -> SetUserPrivacySettingRules
$cfrom :: forall x.
SetUserPrivacySettingRules -> Rep SetUserPrivacySettingRules x
Generic)

-- | Parameter of Function getUserPrivacySettingRules
data GetUserPrivacySettingRules
  = -- | Returns the current privacy settings
    GetUserPrivacySettingRules
      { -- | The privacy setting
        GetUserPrivacySettingRules -> UserPrivacySetting
setting :: UserPrivacySetting
      }
  deriving (Int -> GetUserPrivacySettingRules -> ShowS
[GetUserPrivacySettingRules] -> ShowS
GetUserPrivacySettingRules -> String
(Int -> GetUserPrivacySettingRules -> ShowS)
-> (GetUserPrivacySettingRules -> String)
-> ([GetUserPrivacySettingRules] -> ShowS)
-> Show GetUserPrivacySettingRules
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetUserPrivacySettingRules] -> ShowS
$cshowList :: [GetUserPrivacySettingRules] -> ShowS
show :: GetUserPrivacySettingRules -> String
$cshow :: GetUserPrivacySettingRules -> String
showsPrec :: Int -> GetUserPrivacySettingRules -> ShowS
$cshowsPrec :: Int -> GetUserPrivacySettingRules -> ShowS
Show, GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool
(GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool)
-> (GetUserPrivacySettingRules
    -> GetUserPrivacySettingRules -> Bool)
-> Eq GetUserPrivacySettingRules
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool
$c/= :: GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool
== :: GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool
$c== :: GetUserPrivacySettingRules -> GetUserPrivacySettingRules -> Bool
Eq, (forall x.
 GetUserPrivacySettingRules -> Rep GetUserPrivacySettingRules x)
-> (forall x.
    Rep GetUserPrivacySettingRules x -> GetUserPrivacySettingRules)
-> Generic GetUserPrivacySettingRules
forall x.
Rep GetUserPrivacySettingRules x -> GetUserPrivacySettingRules
forall x.
GetUserPrivacySettingRules -> Rep GetUserPrivacySettingRules x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetUserPrivacySettingRules x -> GetUserPrivacySettingRules
$cfrom :: forall x.
GetUserPrivacySettingRules -> Rep GetUserPrivacySettingRules x
Generic)

-- | Parameter of Function getOption
data GetOption
  = -- | Returns the value of an option by its name. (Check the list of available options on https://core.telegram.org/tdlib/options.) Can be called before authorization
    GetOption
      { -- | The name of the option
        GetOption -> T
name :: T
      }
  deriving (Int -> GetOption -> ShowS
[GetOption] -> ShowS
GetOption -> String
(Int -> GetOption -> ShowS)
-> (GetOption -> String)
-> ([GetOption] -> ShowS)
-> Show GetOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetOption] -> ShowS
$cshowList :: [GetOption] -> ShowS
show :: GetOption -> String
$cshow :: GetOption -> String
showsPrec :: Int -> GetOption -> ShowS
$cshowsPrec :: Int -> GetOption -> ShowS
Show, GetOption -> GetOption -> Bool
(GetOption -> GetOption -> Bool)
-> (GetOption -> GetOption -> Bool) -> Eq GetOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetOption -> GetOption -> Bool
$c/= :: GetOption -> GetOption -> Bool
== :: GetOption -> GetOption -> Bool
$c== :: GetOption -> GetOption -> Bool
Eq, (forall x. GetOption -> Rep GetOption x)
-> (forall x. Rep GetOption x -> GetOption) -> Generic GetOption
forall x. Rep GetOption x -> GetOption
forall x. GetOption -> Rep GetOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetOption x -> GetOption
$cfrom :: forall x. GetOption -> Rep GetOption x
Generic)

-- | Parameter of Function setOption
data SetOption
  = -- | Sets the value of an option. (Check the list of available options on https://core.telegram.org/tdlib/options.) Only writable options can be set. Can be called before authorization
    SetOption
      { -- | The name of the option
        SetOption -> T
name :: T,
        -- | The new value of the option
        SetOption -> OptionValue
value :: OptionValue
      }
  deriving (Int -> SetOption -> ShowS
[SetOption] -> ShowS
SetOption -> String
(Int -> SetOption -> ShowS)
-> (SetOption -> String)
-> ([SetOption] -> ShowS)
-> Show SetOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetOption] -> ShowS
$cshowList :: [SetOption] -> ShowS
show :: SetOption -> String
$cshow :: SetOption -> String
showsPrec :: Int -> SetOption -> ShowS
$cshowsPrec :: Int -> SetOption -> ShowS
Show, SetOption -> SetOption -> Bool
(SetOption -> SetOption -> Bool)
-> (SetOption -> SetOption -> Bool) -> Eq SetOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetOption -> SetOption -> Bool
$c/= :: SetOption -> SetOption -> Bool
== :: SetOption -> SetOption -> Bool
$c== :: SetOption -> SetOption -> Bool
Eq, (forall x. SetOption -> Rep SetOption x)
-> (forall x. Rep SetOption x -> SetOption) -> Generic SetOption
forall x. Rep SetOption x -> SetOption
forall x. SetOption -> Rep SetOption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetOption x -> SetOption
$cfrom :: forall x. SetOption -> Rep SetOption x
Generic)

-- | Parameter of Function setAccountTtl
data SetAccountTtl
  = -- | Changes the period of inactivity after which the account of the current user will automatically be deleted
    SetAccountTtl
      { -- | New account TTL
        SetAccountTtl -> AccountTtl
ttl :: AccountTtl
      }
  deriving (Int -> SetAccountTtl -> ShowS
[SetAccountTtl] -> ShowS
SetAccountTtl -> String
(Int -> SetAccountTtl -> ShowS)
-> (SetAccountTtl -> String)
-> ([SetAccountTtl] -> ShowS)
-> Show SetAccountTtl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetAccountTtl] -> ShowS
$cshowList :: [SetAccountTtl] -> ShowS
show :: SetAccountTtl -> String
$cshow :: SetAccountTtl -> String
showsPrec :: Int -> SetAccountTtl -> ShowS
$cshowsPrec :: Int -> SetAccountTtl -> ShowS
Show, SetAccountTtl -> SetAccountTtl -> Bool
(SetAccountTtl -> SetAccountTtl -> Bool)
-> (SetAccountTtl -> SetAccountTtl -> Bool) -> Eq SetAccountTtl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetAccountTtl -> SetAccountTtl -> Bool
$c/= :: SetAccountTtl -> SetAccountTtl -> Bool
== :: SetAccountTtl -> SetAccountTtl -> Bool
$c== :: SetAccountTtl -> SetAccountTtl -> Bool
Eq, (forall x. SetAccountTtl -> Rep SetAccountTtl x)
-> (forall x. Rep SetAccountTtl x -> SetAccountTtl)
-> Generic SetAccountTtl
forall x. Rep SetAccountTtl x -> SetAccountTtl
forall x. SetAccountTtl -> Rep SetAccountTtl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetAccountTtl x -> SetAccountTtl
$cfrom :: forall x. SetAccountTtl -> Rep SetAccountTtl x
Generic)

-- | Parameter of Function getAccountTtl
data GetAccountTtl
  = -- | Returns the period of inactivity after which the account of the current user will automatically be deleted
    GetAccountTtl
      {
      }
  deriving (Int -> GetAccountTtl -> ShowS
[GetAccountTtl] -> ShowS
GetAccountTtl -> String
(Int -> GetAccountTtl -> ShowS)
-> (GetAccountTtl -> String)
-> ([GetAccountTtl] -> ShowS)
-> Show GetAccountTtl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAccountTtl] -> ShowS
$cshowList :: [GetAccountTtl] -> ShowS
show :: GetAccountTtl -> String
$cshow :: GetAccountTtl -> String
showsPrec :: Int -> GetAccountTtl -> ShowS
$cshowsPrec :: Int -> GetAccountTtl -> ShowS
Show, GetAccountTtl -> GetAccountTtl -> Bool
(GetAccountTtl -> GetAccountTtl -> Bool)
-> (GetAccountTtl -> GetAccountTtl -> Bool) -> Eq GetAccountTtl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAccountTtl -> GetAccountTtl -> Bool
$c/= :: GetAccountTtl -> GetAccountTtl -> Bool
== :: GetAccountTtl -> GetAccountTtl -> Bool
$c== :: GetAccountTtl -> GetAccountTtl -> Bool
Eq, (forall x. GetAccountTtl -> Rep GetAccountTtl x)
-> (forall x. Rep GetAccountTtl x -> GetAccountTtl)
-> Generic GetAccountTtl
forall x. Rep GetAccountTtl x -> GetAccountTtl
forall x. GetAccountTtl -> Rep GetAccountTtl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAccountTtl x -> GetAccountTtl
$cfrom :: forall x. GetAccountTtl -> Rep GetAccountTtl x
Generic)

-- | Parameter of Function deleteAccount
data DeleteAccount
  = -- | Deletes the account of the current user, deleting all information associated with the user from the server. The phone number of the account can be used to create a new account. Can be called before authorization when the current authorization state is authorizationStateWaitPassword
    DeleteAccount
      { -- | The reason why the account was deleted; optional
        DeleteAccount -> T
reason :: T
      }
  deriving (Int -> DeleteAccount -> ShowS
[DeleteAccount] -> ShowS
DeleteAccount -> String
(Int -> DeleteAccount -> ShowS)
-> (DeleteAccount -> String)
-> ([DeleteAccount] -> ShowS)
-> Show DeleteAccount
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccount] -> ShowS
$cshowList :: [DeleteAccount] -> ShowS
show :: DeleteAccount -> String
$cshow :: DeleteAccount -> String
showsPrec :: Int -> DeleteAccount -> ShowS
$cshowsPrec :: Int -> DeleteAccount -> ShowS
Show, DeleteAccount -> DeleteAccount -> Bool
(DeleteAccount -> DeleteAccount -> Bool)
-> (DeleteAccount -> DeleteAccount -> Bool) -> Eq DeleteAccount
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccount -> DeleteAccount -> Bool
$c/= :: DeleteAccount -> DeleteAccount -> Bool
== :: DeleteAccount -> DeleteAccount -> Bool
$c== :: DeleteAccount -> DeleteAccount -> Bool
Eq, (forall x. DeleteAccount -> Rep DeleteAccount x)
-> (forall x. Rep DeleteAccount x -> DeleteAccount)
-> Generic DeleteAccount
forall x. Rep DeleteAccount x -> DeleteAccount
forall x. DeleteAccount -> Rep DeleteAccount x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAccount x -> DeleteAccount
$cfrom :: forall x. DeleteAccount -> Rep DeleteAccount x
Generic)

-- | Parameter of Function removeChatActionBar
data RemoveChatActionBar
  = -- | Removes a chat action bar without any other action
    RemoveChatActionBar
      { -- | Chat identifier
        RemoveChatActionBar -> Int
chat_id :: I53
      }
  deriving (Int -> RemoveChatActionBar -> ShowS
[RemoveChatActionBar] -> ShowS
RemoveChatActionBar -> String
(Int -> RemoveChatActionBar -> ShowS)
-> (RemoveChatActionBar -> String)
-> ([RemoveChatActionBar] -> ShowS)
-> Show RemoveChatActionBar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveChatActionBar] -> ShowS
$cshowList :: [RemoveChatActionBar] -> ShowS
show :: RemoveChatActionBar -> String
$cshow :: RemoveChatActionBar -> String
showsPrec :: Int -> RemoveChatActionBar -> ShowS
$cshowsPrec :: Int -> RemoveChatActionBar -> ShowS
Show, RemoveChatActionBar -> RemoveChatActionBar -> Bool
(RemoveChatActionBar -> RemoveChatActionBar -> Bool)
-> (RemoveChatActionBar -> RemoveChatActionBar -> Bool)
-> Eq RemoveChatActionBar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveChatActionBar -> RemoveChatActionBar -> Bool
$c/= :: RemoveChatActionBar -> RemoveChatActionBar -> Bool
== :: RemoveChatActionBar -> RemoveChatActionBar -> Bool
$c== :: RemoveChatActionBar -> RemoveChatActionBar -> Bool
Eq, (forall x. RemoveChatActionBar -> Rep RemoveChatActionBar x)
-> (forall x. Rep RemoveChatActionBar x -> RemoveChatActionBar)
-> Generic RemoveChatActionBar
forall x. Rep RemoveChatActionBar x -> RemoveChatActionBar
forall x. RemoveChatActionBar -> Rep RemoveChatActionBar x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveChatActionBar x -> RemoveChatActionBar
$cfrom :: forall x. RemoveChatActionBar -> Rep RemoveChatActionBar x
Generic)

-- | Parameter of Function reportChat
data ReportChat
  = -- | Reports a chat to the Telegram moderators. A chat can be reported only from the chat action bar, or if this is a private chats with a bot, a private chat with a user sharing their location, a supergroup, or a channel, since other chats can't be checked by moderators
    ReportChat
      { -- | Chat identifier
        ReportChat -> Int
chat_id :: I53,
        -- | The reason for reporting the chat
        ReportChat -> ChatReportReason
reason :: ChatReportReason,
        -- | Identifiers of reported messages, if any
        ReportChat -> [Int]
message_ids :: ([]) (I53)
      }
  deriving (Int -> ReportChat -> ShowS
[ReportChat] -> ShowS
ReportChat -> String
(Int -> ReportChat -> ShowS)
-> (ReportChat -> String)
-> ([ReportChat] -> ShowS)
-> Show ReportChat
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ReportChat] -> ShowS
$cshowList :: [ReportChat] -> ShowS
show :: ReportChat -> String
$cshow :: ReportChat -> String
showsPrec :: Int -> ReportChat -> ShowS
$cshowsPrec :: Int -> ReportChat -> ShowS
Show, ReportChat -> ReportChat -> Bool
(ReportChat -> ReportChat -> Bool)
-> (ReportChat -> ReportChat -> Bool) -> Eq ReportChat
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ReportChat -> ReportChat -> Bool
$c/= :: ReportChat -> ReportChat -> Bool
== :: ReportChat -> ReportChat -> Bool
$c== :: ReportChat -> ReportChat -> Bool
Eq, (forall x. ReportChat -> Rep ReportChat x)
-> (forall x. Rep ReportChat x -> ReportChat) -> Generic ReportChat
forall x. Rep ReportChat x -> ReportChat
forall x. ReportChat -> Rep ReportChat x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReportChat x -> ReportChat
$cfrom :: forall x. ReportChat -> Rep ReportChat x
Generic)

-- | Parameter of Function getChatStatisticsUrl
data GetChatStatisticsUrl
  = -- | Returns an HTTP URL with the chat statistics. Currently this method of getting the statistics is disabled and can be deleted in the future
    GetChatStatisticsUrl
      { -- | Chat identifier
        GetChatStatisticsUrl -> Int
chat_id :: I53,
        -- | Parameters from "tg://statsrefresh?params=******" link
        GetChatStatisticsUrl -> T
parameters :: T,
        -- | Pass true if a URL with the dark theme must be returned
        GetChatStatisticsUrl -> Bool
is_dark :: Bool
      }
  deriving (Int -> GetChatStatisticsUrl -> ShowS
[GetChatStatisticsUrl] -> ShowS
GetChatStatisticsUrl -> String
(Int -> GetChatStatisticsUrl -> ShowS)
-> (GetChatStatisticsUrl -> String)
-> ([GetChatStatisticsUrl] -> ShowS)
-> Show GetChatStatisticsUrl
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatStatisticsUrl] -> ShowS
$cshowList :: [GetChatStatisticsUrl] -> ShowS
show :: GetChatStatisticsUrl -> String
$cshow :: GetChatStatisticsUrl -> String
showsPrec :: Int -> GetChatStatisticsUrl -> ShowS
$cshowsPrec :: Int -> GetChatStatisticsUrl -> ShowS
Show, GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool
(GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool)
-> (GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool)
-> Eq GetChatStatisticsUrl
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool
$c/= :: GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool
== :: GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool
$c== :: GetChatStatisticsUrl -> GetChatStatisticsUrl -> Bool
Eq, (forall x. GetChatStatisticsUrl -> Rep GetChatStatisticsUrl x)
-> (forall x. Rep GetChatStatisticsUrl x -> GetChatStatisticsUrl)
-> Generic GetChatStatisticsUrl
forall x. Rep GetChatStatisticsUrl x -> GetChatStatisticsUrl
forall x. GetChatStatisticsUrl -> Rep GetChatStatisticsUrl x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatStatisticsUrl x -> GetChatStatisticsUrl
$cfrom :: forall x. GetChatStatisticsUrl -> Rep GetChatStatisticsUrl x
Generic)

-- | Parameter of Function getChatStatistics
data GetChatStatistics
  = -- | Returns detailed statistics about a chat. Currently this method can be used only for channels. Requires administrator rights in the channel
    GetChatStatistics
      { -- | Chat identifier
        GetChatStatistics -> Int
chat_id :: I53,
        -- | Pass true if a dark theme is used by the app
        GetChatStatistics -> Bool
is_dark :: Bool
      }
  deriving (Int -> GetChatStatistics -> ShowS
[GetChatStatistics] -> ShowS
GetChatStatistics -> String
(Int -> GetChatStatistics -> ShowS)
-> (GetChatStatistics -> String)
-> ([GetChatStatistics] -> ShowS)
-> Show GetChatStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatStatistics] -> ShowS
$cshowList :: [GetChatStatistics] -> ShowS
show :: GetChatStatistics -> String
$cshow :: GetChatStatistics -> String
showsPrec :: Int -> GetChatStatistics -> ShowS
$cshowsPrec :: Int -> GetChatStatistics -> ShowS
Show, GetChatStatistics -> GetChatStatistics -> Bool
(GetChatStatistics -> GetChatStatistics -> Bool)
-> (GetChatStatistics -> GetChatStatistics -> Bool)
-> Eq GetChatStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatStatistics -> GetChatStatistics -> Bool
$c/= :: GetChatStatistics -> GetChatStatistics -> Bool
== :: GetChatStatistics -> GetChatStatistics -> Bool
$c== :: GetChatStatistics -> GetChatStatistics -> Bool
Eq, (forall x. GetChatStatistics -> Rep GetChatStatistics x)
-> (forall x. Rep GetChatStatistics x -> GetChatStatistics)
-> Generic GetChatStatistics
forall x. Rep GetChatStatistics x -> GetChatStatistics
forall x. GetChatStatistics -> Rep GetChatStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatStatistics x -> GetChatStatistics
$cfrom :: forall x. GetChatStatistics -> Rep GetChatStatistics x
Generic)

-- | Parameter of Function getChatStatisticsGraph
data GetChatStatisticsGraph
  = -- | Loads asynchronous or zoomed in chat statistics graph
    GetChatStatisticsGraph
      { -- | Chat identifier
        GetChatStatisticsGraph -> Int
chat_id :: I53,
        -- | The token for graph loading
        GetChatStatisticsGraph -> T
token :: T,
        -- | X-value for zoomed in graph or 0 otherwise
        GetChatStatisticsGraph -> Int
x :: I53
      }
  deriving (Int -> GetChatStatisticsGraph -> ShowS
[GetChatStatisticsGraph] -> ShowS
GetChatStatisticsGraph -> String
(Int -> GetChatStatisticsGraph -> ShowS)
-> (GetChatStatisticsGraph -> String)
-> ([GetChatStatisticsGraph] -> ShowS)
-> Show GetChatStatisticsGraph
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetChatStatisticsGraph] -> ShowS
$cshowList :: [GetChatStatisticsGraph] -> ShowS
show :: GetChatStatisticsGraph -> String
$cshow :: GetChatStatisticsGraph -> String
showsPrec :: Int -> GetChatStatisticsGraph -> ShowS
$cshowsPrec :: Int -> GetChatStatisticsGraph -> ShowS
Show, GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool
(GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool)
-> (GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool)
-> Eq GetChatStatisticsGraph
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool
$c/= :: GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool
== :: GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool
$c== :: GetChatStatisticsGraph -> GetChatStatisticsGraph -> Bool
Eq, (forall x. GetChatStatisticsGraph -> Rep GetChatStatisticsGraph x)
-> (forall x.
    Rep GetChatStatisticsGraph x -> GetChatStatisticsGraph)
-> Generic GetChatStatisticsGraph
forall x. Rep GetChatStatisticsGraph x -> GetChatStatisticsGraph
forall x. GetChatStatisticsGraph -> Rep GetChatStatisticsGraph x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetChatStatisticsGraph x -> GetChatStatisticsGraph
$cfrom :: forall x. GetChatStatisticsGraph -> Rep GetChatStatisticsGraph x
Generic)

-- | Parameter of Function getStorageStatistics
data GetStorageStatistics
  = -- | Returns storage usage statistics. Can be called before authorization
    GetStorageStatistics
      { -- | The maximum number of chats with the largest storage usage for which separate statistics should be returned. All other chats will be grouped in entries with chat_id == 0. If the chat info database is not used, the chat_limit is ignored and is always set to 0
        GetStorageStatistics -> Int
chat_limit :: I32
      }
  deriving (Int -> GetStorageStatistics -> ShowS
[GetStorageStatistics] -> ShowS
GetStorageStatistics -> String
(Int -> GetStorageStatistics -> ShowS)
-> (GetStorageStatistics -> String)
-> ([GetStorageStatistics] -> ShowS)
-> Show GetStorageStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStorageStatistics] -> ShowS
$cshowList :: [GetStorageStatistics] -> ShowS
show :: GetStorageStatistics -> String
$cshow :: GetStorageStatistics -> String
showsPrec :: Int -> GetStorageStatistics -> ShowS
$cshowsPrec :: Int -> GetStorageStatistics -> ShowS
Show, GetStorageStatistics -> GetStorageStatistics -> Bool
(GetStorageStatistics -> GetStorageStatistics -> Bool)
-> (GetStorageStatistics -> GetStorageStatistics -> Bool)
-> Eq GetStorageStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStorageStatistics -> GetStorageStatistics -> Bool
$c/= :: GetStorageStatistics -> GetStorageStatistics -> Bool
== :: GetStorageStatistics -> GetStorageStatistics -> Bool
$c== :: GetStorageStatistics -> GetStorageStatistics -> Bool
Eq, (forall x. GetStorageStatistics -> Rep GetStorageStatistics x)
-> (forall x. Rep GetStorageStatistics x -> GetStorageStatistics)
-> Generic GetStorageStatistics
forall x. Rep GetStorageStatistics x -> GetStorageStatistics
forall x. GetStorageStatistics -> Rep GetStorageStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetStorageStatistics x -> GetStorageStatistics
$cfrom :: forall x. GetStorageStatistics -> Rep GetStorageStatistics x
Generic)

-- | Parameter of Function getStorageStatisticsFast
data GetStorageStatisticsFast
  = -- | Quickly returns approximate storage usage statistics. Can be called before authorization
    GetStorageStatisticsFast
      {
      }
  deriving (Int -> GetStorageStatisticsFast -> ShowS
[GetStorageStatisticsFast] -> ShowS
GetStorageStatisticsFast -> String
(Int -> GetStorageStatisticsFast -> ShowS)
-> (GetStorageStatisticsFast -> String)
-> ([GetStorageStatisticsFast] -> ShowS)
-> Show GetStorageStatisticsFast
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetStorageStatisticsFast] -> ShowS
$cshowList :: [GetStorageStatisticsFast] -> ShowS
show :: GetStorageStatisticsFast -> String
$cshow :: GetStorageStatisticsFast -> String
showsPrec :: Int -> GetStorageStatisticsFast -> ShowS
$cshowsPrec :: Int -> GetStorageStatisticsFast -> ShowS
Show, GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool
(GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool)
-> (GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool)
-> Eq GetStorageStatisticsFast
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool
$c/= :: GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool
== :: GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool
$c== :: GetStorageStatisticsFast -> GetStorageStatisticsFast -> Bool
Eq, (forall x.
 GetStorageStatisticsFast -> Rep GetStorageStatisticsFast x)
-> (forall x.
    Rep GetStorageStatisticsFast x -> GetStorageStatisticsFast)
-> Generic GetStorageStatisticsFast
forall x.
Rep GetStorageStatisticsFast x -> GetStorageStatisticsFast
forall x.
GetStorageStatisticsFast -> Rep GetStorageStatisticsFast x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetStorageStatisticsFast x -> GetStorageStatisticsFast
$cfrom :: forall x.
GetStorageStatisticsFast -> Rep GetStorageStatisticsFast x
Generic)

-- | Parameter of Function getDatabaseStatistics
data GetDatabaseStatistics
  = -- | Returns database statistics
    GetDatabaseStatistics
      {
      }
  deriving (Int -> GetDatabaseStatistics -> ShowS
[GetDatabaseStatistics] -> ShowS
GetDatabaseStatistics -> String
(Int -> GetDatabaseStatistics -> ShowS)
-> (GetDatabaseStatistics -> String)
-> ([GetDatabaseStatistics] -> ShowS)
-> Show GetDatabaseStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDatabaseStatistics] -> ShowS
$cshowList :: [GetDatabaseStatistics] -> ShowS
show :: GetDatabaseStatistics -> String
$cshow :: GetDatabaseStatistics -> String
showsPrec :: Int -> GetDatabaseStatistics -> ShowS
$cshowsPrec :: Int -> GetDatabaseStatistics -> ShowS
Show, GetDatabaseStatistics -> GetDatabaseStatistics -> Bool
(GetDatabaseStatistics -> GetDatabaseStatistics -> Bool)
-> (GetDatabaseStatistics -> GetDatabaseStatistics -> Bool)
-> Eq GetDatabaseStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDatabaseStatistics -> GetDatabaseStatistics -> Bool
$c/= :: GetDatabaseStatistics -> GetDatabaseStatistics -> Bool
== :: GetDatabaseStatistics -> GetDatabaseStatistics -> Bool
$c== :: GetDatabaseStatistics -> GetDatabaseStatistics -> Bool
Eq, (forall x. GetDatabaseStatistics -> Rep GetDatabaseStatistics x)
-> (forall x. Rep GetDatabaseStatistics x -> GetDatabaseStatistics)
-> Generic GetDatabaseStatistics
forall x. Rep GetDatabaseStatistics x -> GetDatabaseStatistics
forall x. GetDatabaseStatistics -> Rep GetDatabaseStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDatabaseStatistics x -> GetDatabaseStatistics
$cfrom :: forall x. GetDatabaseStatistics -> Rep GetDatabaseStatistics x
Generic)

-- | Parameter of Function optimizeStorage
data OptimizeStorage
  = -- | Optimizes storage usage, i.e. deletes some files and returns new storage usage statistics. Secret thumbnails can't be deleted
    OptimizeStorage
      { -- | Limit on the total size of files after deletion. Pass -1 to use the default limit
        OptimizeStorage -> Int
size :: I53,
        -- | Limit on the time that has passed since the last time a file was accessed (or creation time for some filesystems). Pass -1 to use the default limit
        OptimizeStorage -> Int
ttl :: I32,
        -- | Limit on the total count of files after deletion. Pass -1 to use the default limit
        OptimizeStorage -> Int
count :: I32,
        -- | The amount of time after the creation of a file during which it can't be deleted, in seconds. Pass -1 to use the default value
        OptimizeStorage -> Int
immunity_delay :: I32,
        -- | If not empty, only files with the given type(s) are considered. By default, all types except thumbnails, profile photos, stickers and wallpapers are deleted
        OptimizeStorage -> [FileType]
file_types :: ([]) (FileType),
        -- | If not empty, only files from the given chats are considered. Use 0 as chat identifier to delete files not belonging to any chat (e.g., profile photos)
        OptimizeStorage -> [Int]
chat_ids :: ([]) (I53),
        -- | If not empty, files from the given chats are excluded. Use 0 as chat identifier to exclude all files not belonging to any chat (e.g., profile photos)
        OptimizeStorage -> [Int]
exclude_chat_ids :: ([]) (I53),
        -- | Pass true if deleted file statistics needs to be returned instead of the whole storage usage statistics. Affects only returned statistics
        OptimizeStorage -> Bool
return_deleted_file_statistics :: Bool,
        -- | Same as in getStorageStatistics. Affects only returned statistics
        OptimizeStorage -> Int
chat_limit :: I32
      }
  deriving (Int -> OptimizeStorage -> ShowS
[OptimizeStorage] -> ShowS
OptimizeStorage -> String
(Int -> OptimizeStorage -> ShowS)
-> (OptimizeStorage -> String)
-> ([OptimizeStorage] -> ShowS)
-> Show OptimizeStorage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OptimizeStorage] -> ShowS
$cshowList :: [OptimizeStorage] -> ShowS
show :: OptimizeStorage -> String
$cshow :: OptimizeStorage -> String
showsPrec :: Int -> OptimizeStorage -> ShowS
$cshowsPrec :: Int -> OptimizeStorage -> ShowS
Show, OptimizeStorage -> OptimizeStorage -> Bool
(OptimizeStorage -> OptimizeStorage -> Bool)
-> (OptimizeStorage -> OptimizeStorage -> Bool)
-> Eq OptimizeStorage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OptimizeStorage -> OptimizeStorage -> Bool
$c/= :: OptimizeStorage -> OptimizeStorage -> Bool
== :: OptimizeStorage -> OptimizeStorage -> Bool
$c== :: OptimizeStorage -> OptimizeStorage -> Bool
Eq, (forall x. OptimizeStorage -> Rep OptimizeStorage x)
-> (forall x. Rep OptimizeStorage x -> OptimizeStorage)
-> Generic OptimizeStorage
forall x. Rep OptimizeStorage x -> OptimizeStorage
forall x. OptimizeStorage -> Rep OptimizeStorage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep OptimizeStorage x -> OptimizeStorage
$cfrom :: forall x. OptimizeStorage -> Rep OptimizeStorage x
Generic)

-- | Parameter of Function setNetworkType
data SetNetworkType
  = -- | Sets the current network type. Can be called before authorization. Calling this method forces all network connections to reopen, mitigating the delay in switching between different networks, so it should be called whenever the network is changed, even if the network type remains the same.
    SetNetworkType
      { SetNetworkType -> NetworkType
type_ :: NetworkType
      }
  deriving (Int -> SetNetworkType -> ShowS
[SetNetworkType] -> ShowS
SetNetworkType -> String
(Int -> SetNetworkType -> ShowS)
-> (SetNetworkType -> String)
-> ([SetNetworkType] -> ShowS)
-> Show SetNetworkType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetNetworkType] -> ShowS
$cshowList :: [SetNetworkType] -> ShowS
show :: SetNetworkType -> String
$cshow :: SetNetworkType -> String
showsPrec :: Int -> SetNetworkType -> ShowS
$cshowsPrec :: Int -> SetNetworkType -> ShowS
Show, SetNetworkType -> SetNetworkType -> Bool
(SetNetworkType -> SetNetworkType -> Bool)
-> (SetNetworkType -> SetNetworkType -> Bool) -> Eq SetNetworkType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetNetworkType -> SetNetworkType -> Bool
$c/= :: SetNetworkType -> SetNetworkType -> Bool
== :: SetNetworkType -> SetNetworkType -> Bool
$c== :: SetNetworkType -> SetNetworkType -> Bool
Eq, (forall x. SetNetworkType -> Rep SetNetworkType x)
-> (forall x. Rep SetNetworkType x -> SetNetworkType)
-> Generic SetNetworkType
forall x. Rep SetNetworkType x -> SetNetworkType
forall x. SetNetworkType -> Rep SetNetworkType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetNetworkType x -> SetNetworkType
$cfrom :: forall x. SetNetworkType -> Rep SetNetworkType x
Generic)

-- | Parameter of Function getNetworkStatistics
data GetNetworkStatistics
  = -- | Returns network data usage statistics. Can be called before authorization
    GetNetworkStatistics
      { -- | If true, returns only data for the current library launch
        GetNetworkStatistics -> Bool
only_current :: Bool
      }
  deriving (Int -> GetNetworkStatistics -> ShowS
[GetNetworkStatistics] -> ShowS
GetNetworkStatistics -> String
(Int -> GetNetworkStatistics -> ShowS)
-> (GetNetworkStatistics -> String)
-> ([GetNetworkStatistics] -> ShowS)
-> Show GetNetworkStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetNetworkStatistics] -> ShowS
$cshowList :: [GetNetworkStatistics] -> ShowS
show :: GetNetworkStatistics -> String
$cshow :: GetNetworkStatistics -> String
showsPrec :: Int -> GetNetworkStatistics -> ShowS
$cshowsPrec :: Int -> GetNetworkStatistics -> ShowS
Show, GetNetworkStatistics -> GetNetworkStatistics -> Bool
(GetNetworkStatistics -> GetNetworkStatistics -> Bool)
-> (GetNetworkStatistics -> GetNetworkStatistics -> Bool)
-> Eq GetNetworkStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetNetworkStatistics -> GetNetworkStatistics -> Bool
$c/= :: GetNetworkStatistics -> GetNetworkStatistics -> Bool
== :: GetNetworkStatistics -> GetNetworkStatistics -> Bool
$c== :: GetNetworkStatistics -> GetNetworkStatistics -> Bool
Eq, (forall x. GetNetworkStatistics -> Rep GetNetworkStatistics x)
-> (forall x. Rep GetNetworkStatistics x -> GetNetworkStatistics)
-> Generic GetNetworkStatistics
forall x. Rep GetNetworkStatistics x -> GetNetworkStatistics
forall x. GetNetworkStatistics -> Rep GetNetworkStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetNetworkStatistics x -> GetNetworkStatistics
$cfrom :: forall x. GetNetworkStatistics -> Rep GetNetworkStatistics x
Generic)

-- | Parameter of Function addNetworkStatistics
data AddNetworkStatistics
  = -- | Adds the specified data to data usage statistics. Can be called before authorization
    AddNetworkStatistics
      { -- | The network statistics entry with the data to be added to statistics
        AddNetworkStatistics -> NetworkStatisticsEntry
entry :: NetworkStatisticsEntry
      }
  deriving (Int -> AddNetworkStatistics -> ShowS
[AddNetworkStatistics] -> ShowS
AddNetworkStatistics -> String
(Int -> AddNetworkStatistics -> ShowS)
-> (AddNetworkStatistics -> String)
-> ([AddNetworkStatistics] -> ShowS)
-> Show AddNetworkStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddNetworkStatistics] -> ShowS
$cshowList :: [AddNetworkStatistics] -> ShowS
show :: AddNetworkStatistics -> String
$cshow :: AddNetworkStatistics -> String
showsPrec :: Int -> AddNetworkStatistics -> ShowS
$cshowsPrec :: Int -> AddNetworkStatistics -> ShowS
Show, AddNetworkStatistics -> AddNetworkStatistics -> Bool
(AddNetworkStatistics -> AddNetworkStatistics -> Bool)
-> (AddNetworkStatistics -> AddNetworkStatistics -> Bool)
-> Eq AddNetworkStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddNetworkStatistics -> AddNetworkStatistics -> Bool
$c/= :: AddNetworkStatistics -> AddNetworkStatistics -> Bool
== :: AddNetworkStatistics -> AddNetworkStatistics -> Bool
$c== :: AddNetworkStatistics -> AddNetworkStatistics -> Bool
Eq, (forall x. AddNetworkStatistics -> Rep AddNetworkStatistics x)
-> (forall x. Rep AddNetworkStatistics x -> AddNetworkStatistics)
-> Generic AddNetworkStatistics
forall x. Rep AddNetworkStatistics x -> AddNetworkStatistics
forall x. AddNetworkStatistics -> Rep AddNetworkStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddNetworkStatistics x -> AddNetworkStatistics
$cfrom :: forall x. AddNetworkStatistics -> Rep AddNetworkStatistics x
Generic)

-- | Parameter of Function resetNetworkStatistics
data ResetNetworkStatistics
  = -- | Resets all network data usage statistics to zero. Can be called before authorization
    ResetNetworkStatistics
      {
      }
  deriving (Int -> ResetNetworkStatistics -> ShowS
[ResetNetworkStatistics] -> ShowS
ResetNetworkStatistics -> String
(Int -> ResetNetworkStatistics -> ShowS)
-> (ResetNetworkStatistics -> String)
-> ([ResetNetworkStatistics] -> ShowS)
-> Show ResetNetworkStatistics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResetNetworkStatistics] -> ShowS
$cshowList :: [ResetNetworkStatistics] -> ShowS
show :: ResetNetworkStatistics -> String
$cshow :: ResetNetworkStatistics -> String
showsPrec :: Int -> ResetNetworkStatistics -> ShowS
$cshowsPrec :: Int -> ResetNetworkStatistics -> ShowS
Show, ResetNetworkStatistics -> ResetNetworkStatistics -> Bool
(ResetNetworkStatistics -> ResetNetworkStatistics -> Bool)
-> (ResetNetworkStatistics -> ResetNetworkStatistics -> Bool)
-> Eq ResetNetworkStatistics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResetNetworkStatistics -> ResetNetworkStatistics -> Bool
$c/= :: ResetNetworkStatistics -> ResetNetworkStatistics -> Bool
== :: ResetNetworkStatistics -> ResetNetworkStatistics -> Bool
$c== :: ResetNetworkStatistics -> ResetNetworkStatistics -> Bool
Eq, (forall x. ResetNetworkStatistics -> Rep ResetNetworkStatistics x)
-> (forall x.
    Rep ResetNetworkStatistics x -> ResetNetworkStatistics)
-> Generic ResetNetworkStatistics
forall x. Rep ResetNetworkStatistics x -> ResetNetworkStatistics
forall x. ResetNetworkStatistics -> Rep ResetNetworkStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ResetNetworkStatistics x -> ResetNetworkStatistics
$cfrom :: forall x. ResetNetworkStatistics -> Rep ResetNetworkStatistics x
Generic)

-- | Parameter of Function getAutoDownloadSettingsPresets
data GetAutoDownloadSettingsPresets
  = -- | Returns auto-download settings presets for the current user
    GetAutoDownloadSettingsPresets
      {
      }
  deriving (Int -> GetAutoDownloadSettingsPresets -> ShowS
[GetAutoDownloadSettingsPresets] -> ShowS
GetAutoDownloadSettingsPresets -> String
(Int -> GetAutoDownloadSettingsPresets -> ShowS)
-> (GetAutoDownloadSettingsPresets -> String)
-> ([GetAutoDownloadSettingsPresets] -> ShowS)
-> Show GetAutoDownloadSettingsPresets
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAutoDownloadSettingsPresets] -> ShowS
$cshowList :: [GetAutoDownloadSettingsPresets] -> ShowS
show :: GetAutoDownloadSettingsPresets -> String
$cshow :: GetAutoDownloadSettingsPresets -> String
showsPrec :: Int -> GetAutoDownloadSettingsPresets -> ShowS
$cshowsPrec :: Int -> GetAutoDownloadSettingsPresets -> ShowS
Show, GetAutoDownloadSettingsPresets
-> GetAutoDownloadSettingsPresets -> Bool
(GetAutoDownloadSettingsPresets
 -> GetAutoDownloadSettingsPresets -> Bool)
-> (GetAutoDownloadSettingsPresets
    -> GetAutoDownloadSettingsPresets -> Bool)
-> Eq GetAutoDownloadSettingsPresets
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAutoDownloadSettingsPresets
-> GetAutoDownloadSettingsPresets -> Bool
$c/= :: GetAutoDownloadSettingsPresets
-> GetAutoDownloadSettingsPresets -> Bool
== :: GetAutoDownloadSettingsPresets
-> GetAutoDownloadSettingsPresets -> Bool
$c== :: GetAutoDownloadSettingsPresets
-> GetAutoDownloadSettingsPresets -> Bool
Eq, (forall x.
 GetAutoDownloadSettingsPresets
 -> Rep GetAutoDownloadSettingsPresets x)
-> (forall x.
    Rep GetAutoDownloadSettingsPresets x
    -> GetAutoDownloadSettingsPresets)
-> Generic GetAutoDownloadSettingsPresets
forall x.
Rep GetAutoDownloadSettingsPresets x
-> GetAutoDownloadSettingsPresets
forall x.
GetAutoDownloadSettingsPresets
-> Rep GetAutoDownloadSettingsPresets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAutoDownloadSettingsPresets x
-> GetAutoDownloadSettingsPresets
$cfrom :: forall x.
GetAutoDownloadSettingsPresets
-> Rep GetAutoDownloadSettingsPresets x
Generic)

-- | Parameter of Function setAutoDownloadSettings
data SetAutoDownloadSettings
  = -- | Sets auto-download settings
    SetAutoDownloadSettings
      { -- | New user auto-download settings
        SetAutoDownloadSettings -> AutoDownloadSettings
settings :: AutoDownloadSettings,
        -- | Type of the network for which the new settings are applied
        SetAutoDownloadSettings -> NetworkType
type_ :: NetworkType
      }
  deriving (Int -> SetAutoDownloadSettings -> ShowS
[SetAutoDownloadSettings] -> ShowS
SetAutoDownloadSettings -> String
(Int -> SetAutoDownloadSettings -> ShowS)
-> (SetAutoDownloadSettings -> String)
-> ([SetAutoDownloadSettings] -> ShowS)
-> Show SetAutoDownloadSettings
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetAutoDownloadSettings] -> ShowS
$cshowList :: [SetAutoDownloadSettings] -> ShowS
show :: SetAutoDownloadSettings -> String
$cshow :: SetAutoDownloadSettings -> String
showsPrec :: Int -> SetAutoDownloadSettings -> ShowS
$cshowsPrec :: Int -> SetAutoDownloadSettings -> ShowS
Show, SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool
(SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool)
-> (SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool)
-> Eq SetAutoDownloadSettings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool
$c/= :: SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool
== :: SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool
$c== :: SetAutoDownloadSettings -> SetAutoDownloadSettings -> Bool
Eq, (forall x.
 SetAutoDownloadSettings -> Rep SetAutoDownloadSettings x)
-> (forall x.
    Rep SetAutoDownloadSettings x -> SetAutoDownloadSettings)
-> Generic SetAutoDownloadSettings
forall x. Rep SetAutoDownloadSettings x -> SetAutoDownloadSettings
forall x. SetAutoDownloadSettings -> Rep SetAutoDownloadSettings x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetAutoDownloadSettings x -> SetAutoDownloadSettings
$cfrom :: forall x. SetAutoDownloadSettings -> Rep SetAutoDownloadSettings x
Generic)

-- | Parameter of Function getBankCardInfo
data GetBankCardInfo
  = -- | Returns information about a bank card
    GetBankCardInfo
      { -- | The bank card number
        GetBankCardInfo -> T
bank_card_number :: T
      }
  deriving (Int -> GetBankCardInfo -> ShowS
[GetBankCardInfo] -> ShowS
GetBankCardInfo -> String
(Int -> GetBankCardInfo -> ShowS)
-> (GetBankCardInfo -> String)
-> ([GetBankCardInfo] -> ShowS)
-> Show GetBankCardInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBankCardInfo] -> ShowS
$cshowList :: [GetBankCardInfo] -> ShowS
show :: GetBankCardInfo -> String
$cshow :: GetBankCardInfo -> String
showsPrec :: Int -> GetBankCardInfo -> ShowS
$cshowsPrec :: Int -> GetBankCardInfo -> ShowS
Show, GetBankCardInfo -> GetBankCardInfo -> Bool
(GetBankCardInfo -> GetBankCardInfo -> Bool)
-> (GetBankCardInfo -> GetBankCardInfo -> Bool)
-> Eq GetBankCardInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBankCardInfo -> GetBankCardInfo -> Bool
$c/= :: GetBankCardInfo -> GetBankCardInfo -> Bool
== :: GetBankCardInfo -> GetBankCardInfo -> Bool
$c== :: GetBankCardInfo -> GetBankCardInfo -> Bool
Eq, (forall x. GetBankCardInfo -> Rep GetBankCardInfo x)
-> (forall x. Rep GetBankCardInfo x -> GetBankCardInfo)
-> Generic GetBankCardInfo
forall x. Rep GetBankCardInfo x -> GetBankCardInfo
forall x. GetBankCardInfo -> Rep GetBankCardInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBankCardInfo x -> GetBankCardInfo
$cfrom :: forall x. GetBankCardInfo -> Rep GetBankCardInfo x
Generic)

-- | Parameter of Function getPassportElement
data GetPassportElement
  = -- | Returns one of the available Telegram Passport elements
    GetPassportElement
      { -- | Telegram Passport element type
        GetPassportElement -> PassportElementType
type_ :: PassportElementType,
        -- | Password of the current user
        GetPassportElement -> T
password :: T
      }
  deriving (Int -> GetPassportElement -> ShowS
[GetPassportElement] -> ShowS
GetPassportElement -> String
(Int -> GetPassportElement -> ShowS)
-> (GetPassportElement -> String)
-> ([GetPassportElement] -> ShowS)
-> Show GetPassportElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPassportElement] -> ShowS
$cshowList :: [GetPassportElement] -> ShowS
show :: GetPassportElement -> String
$cshow :: GetPassportElement -> String
showsPrec :: Int -> GetPassportElement -> ShowS
$cshowsPrec :: Int -> GetPassportElement -> ShowS
Show, GetPassportElement -> GetPassportElement -> Bool
(GetPassportElement -> GetPassportElement -> Bool)
-> (GetPassportElement -> GetPassportElement -> Bool)
-> Eq GetPassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPassportElement -> GetPassportElement -> Bool
$c/= :: GetPassportElement -> GetPassportElement -> Bool
== :: GetPassportElement -> GetPassportElement -> Bool
$c== :: GetPassportElement -> GetPassportElement -> Bool
Eq, (forall x. GetPassportElement -> Rep GetPassportElement x)
-> (forall x. Rep GetPassportElement x -> GetPassportElement)
-> Generic GetPassportElement
forall x. Rep GetPassportElement x -> GetPassportElement
forall x. GetPassportElement -> Rep GetPassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetPassportElement x -> GetPassportElement
$cfrom :: forall x. GetPassportElement -> Rep GetPassportElement x
Generic)

-- | Parameter of Function getAllPassportElements
data GetAllPassportElements
  = -- | Returns all available Telegram Passport elements
    GetAllPassportElements
      { -- | Password of the current user
        GetAllPassportElements -> T
password :: T
      }
  deriving (Int -> GetAllPassportElements -> ShowS
[GetAllPassportElements] -> ShowS
GetAllPassportElements -> String
(Int -> GetAllPassportElements -> ShowS)
-> (GetAllPassportElements -> String)
-> ([GetAllPassportElements] -> ShowS)
-> Show GetAllPassportElements
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAllPassportElements] -> ShowS
$cshowList :: [GetAllPassportElements] -> ShowS
show :: GetAllPassportElements -> String
$cshow :: GetAllPassportElements -> String
showsPrec :: Int -> GetAllPassportElements -> ShowS
$cshowsPrec :: Int -> GetAllPassportElements -> ShowS
Show, GetAllPassportElements -> GetAllPassportElements -> Bool
(GetAllPassportElements -> GetAllPassportElements -> Bool)
-> (GetAllPassportElements -> GetAllPassportElements -> Bool)
-> Eq GetAllPassportElements
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAllPassportElements -> GetAllPassportElements -> Bool
$c/= :: GetAllPassportElements -> GetAllPassportElements -> Bool
== :: GetAllPassportElements -> GetAllPassportElements -> Bool
$c== :: GetAllPassportElements -> GetAllPassportElements -> Bool
Eq, (forall x. GetAllPassportElements -> Rep GetAllPassportElements x)
-> (forall x.
    Rep GetAllPassportElements x -> GetAllPassportElements)
-> Generic GetAllPassportElements
forall x. Rep GetAllPassportElements x -> GetAllPassportElements
forall x. GetAllPassportElements -> Rep GetAllPassportElements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetAllPassportElements x -> GetAllPassportElements
$cfrom :: forall x. GetAllPassportElements -> Rep GetAllPassportElements x
Generic)

-- | Parameter of Function setPassportElement
data SetPassportElement
  = -- | Adds an element to the user's Telegram Passport. May return an error with a message "PHONE_VERIFICATION_NEEDED" or "EMAIL_VERIFICATION_NEEDED" if the chosen phone number or the chosen email address must be verified first
    SetPassportElement
      { -- | Input Telegram Passport element
        SetPassportElement -> InputPassportElement
element :: InputPassportElement,
        -- | Password of the current user
        SetPassportElement -> T
password :: T
      }
  deriving (Int -> SetPassportElement -> ShowS
[SetPassportElement] -> ShowS
SetPassportElement -> String
(Int -> SetPassportElement -> ShowS)
-> (SetPassportElement -> String)
-> ([SetPassportElement] -> ShowS)
-> Show SetPassportElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPassportElement] -> ShowS
$cshowList :: [SetPassportElement] -> ShowS
show :: SetPassportElement -> String
$cshow :: SetPassportElement -> String
showsPrec :: Int -> SetPassportElement -> ShowS
$cshowsPrec :: Int -> SetPassportElement -> ShowS
Show, SetPassportElement -> SetPassportElement -> Bool
(SetPassportElement -> SetPassportElement -> Bool)
-> (SetPassportElement -> SetPassportElement -> Bool)
-> Eq SetPassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPassportElement -> SetPassportElement -> Bool
$c/= :: SetPassportElement -> SetPassportElement -> Bool
== :: SetPassportElement -> SetPassportElement -> Bool
$c== :: SetPassportElement -> SetPassportElement -> Bool
Eq, (forall x. SetPassportElement -> Rep SetPassportElement x)
-> (forall x. Rep SetPassportElement x -> SetPassportElement)
-> Generic SetPassportElement
forall x. Rep SetPassportElement x -> SetPassportElement
forall x. SetPassportElement -> Rep SetPassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetPassportElement x -> SetPassportElement
$cfrom :: forall x. SetPassportElement -> Rep SetPassportElement x
Generic)

-- | Parameter of Function deletePassportElement
data DeletePassportElement
  = -- | Deletes a Telegram Passport element
    DeletePassportElement
      { -- | Element type
        DeletePassportElement -> PassportElementType
type_ :: PassportElementType
      }
  deriving (Int -> DeletePassportElement -> ShowS
[DeletePassportElement] -> ShowS
DeletePassportElement -> String
(Int -> DeletePassportElement -> ShowS)
-> (DeletePassportElement -> String)
-> ([DeletePassportElement] -> ShowS)
-> Show DeletePassportElement
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeletePassportElement] -> ShowS
$cshowList :: [DeletePassportElement] -> ShowS
show :: DeletePassportElement -> String
$cshow :: DeletePassportElement -> String
showsPrec :: Int -> DeletePassportElement -> ShowS
$cshowsPrec :: Int -> DeletePassportElement -> ShowS
Show, DeletePassportElement -> DeletePassportElement -> Bool
(DeletePassportElement -> DeletePassportElement -> Bool)
-> (DeletePassportElement -> DeletePassportElement -> Bool)
-> Eq DeletePassportElement
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeletePassportElement -> DeletePassportElement -> Bool
$c/= :: DeletePassportElement -> DeletePassportElement -> Bool
== :: DeletePassportElement -> DeletePassportElement -> Bool
$c== :: DeletePassportElement -> DeletePassportElement -> Bool
Eq, (forall x. DeletePassportElement -> Rep DeletePassportElement x)
-> (forall x. Rep DeletePassportElement x -> DeletePassportElement)
-> Generic DeletePassportElement
forall x. Rep DeletePassportElement x -> DeletePassportElement
forall x. DeletePassportElement -> Rep DeletePassportElement x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeletePassportElement x -> DeletePassportElement
$cfrom :: forall x. DeletePassportElement -> Rep DeletePassportElement x
Generic)

-- | Parameter of Function setPassportElementErrors
data SetPassportElementErrors
  = -- | Informs the user that some of the elements in their Telegram Passport contain errors; for bots only. The user will not be able to resend the elements, until the errors are fixed
    SetPassportElementErrors
      { -- | User identifier
        SetPassportElementErrors -> Int
user_id :: I32,
        -- | The errors
        SetPassportElementErrors -> [InputPassportElementError]
errors :: ([]) (InputPassportElementError)
      }
  deriving (Int -> SetPassportElementErrors -> ShowS
[SetPassportElementErrors] -> ShowS
SetPassportElementErrors -> String
(Int -> SetPassportElementErrors -> ShowS)
-> (SetPassportElementErrors -> String)
-> ([SetPassportElementErrors] -> ShowS)
-> Show SetPassportElementErrors
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetPassportElementErrors] -> ShowS
$cshowList :: [SetPassportElementErrors] -> ShowS
show :: SetPassportElementErrors -> String
$cshow :: SetPassportElementErrors -> String
showsPrec :: Int -> SetPassportElementErrors -> ShowS
$cshowsPrec :: Int -> SetPassportElementErrors -> ShowS
Show, SetPassportElementErrors -> SetPassportElementErrors -> Bool
(SetPassportElementErrors -> SetPassportElementErrors -> Bool)
-> (SetPassportElementErrors -> SetPassportElementErrors -> Bool)
-> Eq SetPassportElementErrors
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetPassportElementErrors -> SetPassportElementErrors -> Bool
$c/= :: SetPassportElementErrors -> SetPassportElementErrors -> Bool
== :: SetPassportElementErrors -> SetPassportElementErrors -> Bool
$c== :: SetPassportElementErrors -> SetPassportElementErrors -> Bool
Eq, (forall x.
 SetPassportElementErrors -> Rep SetPassportElementErrors x)
-> (forall x.
    Rep SetPassportElementErrors x -> SetPassportElementErrors)
-> Generic SetPassportElementErrors
forall x.
Rep SetPassportElementErrors x -> SetPassportElementErrors
forall x.
SetPassportElementErrors -> Rep SetPassportElementErrors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetPassportElementErrors x -> SetPassportElementErrors
$cfrom :: forall x.
SetPassportElementErrors -> Rep SetPassportElementErrors x
Generic)

-- | Parameter of Function getPreferredCountryLanguage
data GetPreferredCountryLanguage
  = -- | Returns an IETF language tag of the language preferred in the country, which should be used to fill native fields in Telegram Passport personal details. Returns a 404 error if unknown
    GetPreferredCountryLanguage
      { -- | A two-letter ISO 3166-1 alpha-2 country code
        GetPreferredCountryLanguage -> T
country_code :: T
      }
  deriving (Int -> GetPreferredCountryLanguage -> ShowS
[GetPreferredCountryLanguage] -> ShowS
GetPreferredCountryLanguage -> String
(Int -> GetPreferredCountryLanguage -> ShowS)
-> (GetPreferredCountryLanguage -> String)
-> ([GetPreferredCountryLanguage] -> ShowS)
-> Show GetPreferredCountryLanguage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPreferredCountryLanguage] -> ShowS
$cshowList :: [GetPreferredCountryLanguage] -> ShowS
show :: GetPreferredCountryLanguage -> String
$cshow :: GetPreferredCountryLanguage -> String
showsPrec :: Int -> GetPreferredCountryLanguage -> ShowS
$cshowsPrec :: Int -> GetPreferredCountryLanguage -> ShowS
Show, GetPreferredCountryLanguage -> GetPreferredCountryLanguage -> Bool
(GetPreferredCountryLanguage
 -> GetPreferredCountryLanguage -> Bool)
-> (GetPreferredCountryLanguage
    -> GetPreferredCountryLanguage -> Bool)
-> Eq GetPreferredCountryLanguage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPreferredCountryLanguage -> GetPreferredCountryLanguage -> Bool
$c/= :: GetPreferredCountryLanguage -> GetPreferredCountryLanguage -> Bool
== :: GetPreferredCountryLanguage -> GetPreferredCountryLanguage -> Bool
$c== :: GetPreferredCountryLanguage -> GetPreferredCountryLanguage -> Bool
Eq, (forall x.
 GetPreferredCountryLanguage -> Rep GetPreferredCountryLanguage x)
-> (forall x.
    Rep GetPreferredCountryLanguage x -> GetPreferredCountryLanguage)
-> Generic GetPreferredCountryLanguage
forall x.
Rep GetPreferredCountryLanguage x -> GetPreferredCountryLanguage
forall x.
GetPreferredCountryLanguage -> Rep GetPreferredCountryLanguage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPreferredCountryLanguage x -> GetPreferredCountryLanguage
$cfrom :: forall x.
GetPreferredCountryLanguage -> Rep GetPreferredCountryLanguage x
Generic)

-- | Parameter of Function sendPhoneNumberVerificationCode
data SendPhoneNumberVerificationCode
  = -- | Sends a code to verify a phone number to be added to a user's Telegram Passport
    SendPhoneNumberVerificationCode
      { -- | The phone number of the user, in international format
        SendPhoneNumberVerificationCode -> T
phone_number :: T,
        -- | Settings for the authentication of the user's phone number
        SendPhoneNumberVerificationCode
-> PhoneNumberAuthenticationSettings
settings :: PhoneNumberAuthenticationSettings
      }
  deriving (Int -> SendPhoneNumberVerificationCode -> ShowS
[SendPhoneNumberVerificationCode] -> ShowS
SendPhoneNumberVerificationCode -> String
(Int -> SendPhoneNumberVerificationCode -> ShowS)
-> (SendPhoneNumberVerificationCode -> String)
-> ([SendPhoneNumberVerificationCode] -> ShowS)
-> Show SendPhoneNumberVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendPhoneNumberVerificationCode] -> ShowS
$cshowList :: [SendPhoneNumberVerificationCode] -> ShowS
show :: SendPhoneNumberVerificationCode -> String
$cshow :: SendPhoneNumberVerificationCode -> String
showsPrec :: Int -> SendPhoneNumberVerificationCode -> ShowS
$cshowsPrec :: Int -> SendPhoneNumberVerificationCode -> ShowS
Show, SendPhoneNumberVerificationCode
-> SendPhoneNumberVerificationCode -> Bool
(SendPhoneNumberVerificationCode
 -> SendPhoneNumberVerificationCode -> Bool)
-> (SendPhoneNumberVerificationCode
    -> SendPhoneNumberVerificationCode -> Bool)
-> Eq SendPhoneNumberVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendPhoneNumberVerificationCode
-> SendPhoneNumberVerificationCode -> Bool
$c/= :: SendPhoneNumberVerificationCode
-> SendPhoneNumberVerificationCode -> Bool
== :: SendPhoneNumberVerificationCode
-> SendPhoneNumberVerificationCode -> Bool
$c== :: SendPhoneNumberVerificationCode
-> SendPhoneNumberVerificationCode -> Bool
Eq, (forall x.
 SendPhoneNumberVerificationCode
 -> Rep SendPhoneNumberVerificationCode x)
-> (forall x.
    Rep SendPhoneNumberVerificationCode x
    -> SendPhoneNumberVerificationCode)
-> Generic SendPhoneNumberVerificationCode
forall x.
Rep SendPhoneNumberVerificationCode x
-> SendPhoneNumberVerificationCode
forall x.
SendPhoneNumberVerificationCode
-> Rep SendPhoneNumberVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendPhoneNumberVerificationCode x
-> SendPhoneNumberVerificationCode
$cfrom :: forall x.
SendPhoneNumberVerificationCode
-> Rep SendPhoneNumberVerificationCode x
Generic)

-- | Parameter of Function resendPhoneNumberVerificationCode
data ResendPhoneNumberVerificationCode
  = -- | Re-sends the code to verify a phone number to be added to a user's Telegram Passport
    ResendPhoneNumberVerificationCode
      {
      }
  deriving (Int -> ResendPhoneNumberVerificationCode -> ShowS
[ResendPhoneNumberVerificationCode] -> ShowS
ResendPhoneNumberVerificationCode -> String
(Int -> ResendPhoneNumberVerificationCode -> ShowS)
-> (ResendPhoneNumberVerificationCode -> String)
-> ([ResendPhoneNumberVerificationCode] -> ShowS)
-> Show ResendPhoneNumberVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendPhoneNumberVerificationCode] -> ShowS
$cshowList :: [ResendPhoneNumberVerificationCode] -> ShowS
show :: ResendPhoneNumberVerificationCode -> String
$cshow :: ResendPhoneNumberVerificationCode -> String
showsPrec :: Int -> ResendPhoneNumberVerificationCode -> ShowS
$cshowsPrec :: Int -> ResendPhoneNumberVerificationCode -> ShowS
Show, ResendPhoneNumberVerificationCode
-> ResendPhoneNumberVerificationCode -> Bool
(ResendPhoneNumberVerificationCode
 -> ResendPhoneNumberVerificationCode -> Bool)
-> (ResendPhoneNumberVerificationCode
    -> ResendPhoneNumberVerificationCode -> Bool)
-> Eq ResendPhoneNumberVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendPhoneNumberVerificationCode
-> ResendPhoneNumberVerificationCode -> Bool
$c/= :: ResendPhoneNumberVerificationCode
-> ResendPhoneNumberVerificationCode -> Bool
== :: ResendPhoneNumberVerificationCode
-> ResendPhoneNumberVerificationCode -> Bool
$c== :: ResendPhoneNumberVerificationCode
-> ResendPhoneNumberVerificationCode -> Bool
Eq, (forall x.
 ResendPhoneNumberVerificationCode
 -> Rep ResendPhoneNumberVerificationCode x)
-> (forall x.
    Rep ResendPhoneNumberVerificationCode x
    -> ResendPhoneNumberVerificationCode)
-> Generic ResendPhoneNumberVerificationCode
forall x.
Rep ResendPhoneNumberVerificationCode x
-> ResendPhoneNumberVerificationCode
forall x.
ResendPhoneNumberVerificationCode
-> Rep ResendPhoneNumberVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendPhoneNumberVerificationCode x
-> ResendPhoneNumberVerificationCode
$cfrom :: forall x.
ResendPhoneNumberVerificationCode
-> Rep ResendPhoneNumberVerificationCode x
Generic)

-- | Parameter of Function checkPhoneNumberVerificationCode
data CheckPhoneNumberVerificationCode
  = -- | Checks the phone number verification code for Telegram Passport
    CheckPhoneNumberVerificationCode
      { -- | Verification code
        CheckPhoneNumberVerificationCode -> T
code :: T
      }
  deriving (Int -> CheckPhoneNumberVerificationCode -> ShowS
[CheckPhoneNumberVerificationCode] -> ShowS
CheckPhoneNumberVerificationCode -> String
(Int -> CheckPhoneNumberVerificationCode -> ShowS)
-> (CheckPhoneNumberVerificationCode -> String)
-> ([CheckPhoneNumberVerificationCode] -> ShowS)
-> Show CheckPhoneNumberVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckPhoneNumberVerificationCode] -> ShowS
$cshowList :: [CheckPhoneNumberVerificationCode] -> ShowS
show :: CheckPhoneNumberVerificationCode -> String
$cshow :: CheckPhoneNumberVerificationCode -> String
showsPrec :: Int -> CheckPhoneNumberVerificationCode -> ShowS
$cshowsPrec :: Int -> CheckPhoneNumberVerificationCode -> ShowS
Show, CheckPhoneNumberVerificationCode
-> CheckPhoneNumberVerificationCode -> Bool
(CheckPhoneNumberVerificationCode
 -> CheckPhoneNumberVerificationCode -> Bool)
-> (CheckPhoneNumberVerificationCode
    -> CheckPhoneNumberVerificationCode -> Bool)
-> Eq CheckPhoneNumberVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckPhoneNumberVerificationCode
-> CheckPhoneNumberVerificationCode -> Bool
$c/= :: CheckPhoneNumberVerificationCode
-> CheckPhoneNumberVerificationCode -> Bool
== :: CheckPhoneNumberVerificationCode
-> CheckPhoneNumberVerificationCode -> Bool
$c== :: CheckPhoneNumberVerificationCode
-> CheckPhoneNumberVerificationCode -> Bool
Eq, (forall x.
 CheckPhoneNumberVerificationCode
 -> Rep CheckPhoneNumberVerificationCode x)
-> (forall x.
    Rep CheckPhoneNumberVerificationCode x
    -> CheckPhoneNumberVerificationCode)
-> Generic CheckPhoneNumberVerificationCode
forall x.
Rep CheckPhoneNumberVerificationCode x
-> CheckPhoneNumberVerificationCode
forall x.
CheckPhoneNumberVerificationCode
-> Rep CheckPhoneNumberVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckPhoneNumberVerificationCode x
-> CheckPhoneNumberVerificationCode
$cfrom :: forall x.
CheckPhoneNumberVerificationCode
-> Rep CheckPhoneNumberVerificationCode x
Generic)

-- | Parameter of Function sendEmailAddressVerificationCode
data SendEmailAddressVerificationCode
  = -- | Sends a code to verify an email address to be added to a user's Telegram Passport
    SendEmailAddressVerificationCode
      { -- | Email address
        SendEmailAddressVerificationCode -> T
email_address :: T
      }
  deriving (Int -> SendEmailAddressVerificationCode -> ShowS
[SendEmailAddressVerificationCode] -> ShowS
SendEmailAddressVerificationCode -> String
(Int -> SendEmailAddressVerificationCode -> ShowS)
-> (SendEmailAddressVerificationCode -> String)
-> ([SendEmailAddressVerificationCode] -> ShowS)
-> Show SendEmailAddressVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendEmailAddressVerificationCode] -> ShowS
$cshowList :: [SendEmailAddressVerificationCode] -> ShowS
show :: SendEmailAddressVerificationCode -> String
$cshow :: SendEmailAddressVerificationCode -> String
showsPrec :: Int -> SendEmailAddressVerificationCode -> ShowS
$cshowsPrec :: Int -> SendEmailAddressVerificationCode -> ShowS
Show, SendEmailAddressVerificationCode
-> SendEmailAddressVerificationCode -> Bool
(SendEmailAddressVerificationCode
 -> SendEmailAddressVerificationCode -> Bool)
-> (SendEmailAddressVerificationCode
    -> SendEmailAddressVerificationCode -> Bool)
-> Eq SendEmailAddressVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendEmailAddressVerificationCode
-> SendEmailAddressVerificationCode -> Bool
$c/= :: SendEmailAddressVerificationCode
-> SendEmailAddressVerificationCode -> Bool
== :: SendEmailAddressVerificationCode
-> SendEmailAddressVerificationCode -> Bool
$c== :: SendEmailAddressVerificationCode
-> SendEmailAddressVerificationCode -> Bool
Eq, (forall x.
 SendEmailAddressVerificationCode
 -> Rep SendEmailAddressVerificationCode x)
-> (forall x.
    Rep SendEmailAddressVerificationCode x
    -> SendEmailAddressVerificationCode)
-> Generic SendEmailAddressVerificationCode
forall x.
Rep SendEmailAddressVerificationCode x
-> SendEmailAddressVerificationCode
forall x.
SendEmailAddressVerificationCode
-> Rep SendEmailAddressVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendEmailAddressVerificationCode x
-> SendEmailAddressVerificationCode
$cfrom :: forall x.
SendEmailAddressVerificationCode
-> Rep SendEmailAddressVerificationCode x
Generic)

-- | Parameter of Function resendEmailAddressVerificationCode
data ResendEmailAddressVerificationCode
  = -- | Re-sends the code to verify an email address to be added to a user's Telegram Passport
    ResendEmailAddressVerificationCode
      {
      }
  deriving (Int -> ResendEmailAddressVerificationCode -> ShowS
[ResendEmailAddressVerificationCode] -> ShowS
ResendEmailAddressVerificationCode -> String
(Int -> ResendEmailAddressVerificationCode -> ShowS)
-> (ResendEmailAddressVerificationCode -> String)
-> ([ResendEmailAddressVerificationCode] -> ShowS)
-> Show ResendEmailAddressVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendEmailAddressVerificationCode] -> ShowS
$cshowList :: [ResendEmailAddressVerificationCode] -> ShowS
show :: ResendEmailAddressVerificationCode -> String
$cshow :: ResendEmailAddressVerificationCode -> String
showsPrec :: Int -> ResendEmailAddressVerificationCode -> ShowS
$cshowsPrec :: Int -> ResendEmailAddressVerificationCode -> ShowS
Show, ResendEmailAddressVerificationCode
-> ResendEmailAddressVerificationCode -> Bool
(ResendEmailAddressVerificationCode
 -> ResendEmailAddressVerificationCode -> Bool)
-> (ResendEmailAddressVerificationCode
    -> ResendEmailAddressVerificationCode -> Bool)
-> Eq ResendEmailAddressVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendEmailAddressVerificationCode
-> ResendEmailAddressVerificationCode -> Bool
$c/= :: ResendEmailAddressVerificationCode
-> ResendEmailAddressVerificationCode -> Bool
== :: ResendEmailAddressVerificationCode
-> ResendEmailAddressVerificationCode -> Bool
$c== :: ResendEmailAddressVerificationCode
-> ResendEmailAddressVerificationCode -> Bool
Eq, (forall x.
 ResendEmailAddressVerificationCode
 -> Rep ResendEmailAddressVerificationCode x)
-> (forall x.
    Rep ResendEmailAddressVerificationCode x
    -> ResendEmailAddressVerificationCode)
-> Generic ResendEmailAddressVerificationCode
forall x.
Rep ResendEmailAddressVerificationCode x
-> ResendEmailAddressVerificationCode
forall x.
ResendEmailAddressVerificationCode
-> Rep ResendEmailAddressVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendEmailAddressVerificationCode x
-> ResendEmailAddressVerificationCode
$cfrom :: forall x.
ResendEmailAddressVerificationCode
-> Rep ResendEmailAddressVerificationCode x
Generic)

-- | Parameter of Function checkEmailAddressVerificationCode
data CheckEmailAddressVerificationCode
  = -- | Checks the email address verification code for Telegram Passport
    CheckEmailAddressVerificationCode
      { -- | Verification code
        CheckEmailAddressVerificationCode -> T
code :: T
      }
  deriving (Int -> CheckEmailAddressVerificationCode -> ShowS
[CheckEmailAddressVerificationCode] -> ShowS
CheckEmailAddressVerificationCode -> String
(Int -> CheckEmailAddressVerificationCode -> ShowS)
-> (CheckEmailAddressVerificationCode -> String)
-> ([CheckEmailAddressVerificationCode] -> ShowS)
-> Show CheckEmailAddressVerificationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckEmailAddressVerificationCode] -> ShowS
$cshowList :: [CheckEmailAddressVerificationCode] -> ShowS
show :: CheckEmailAddressVerificationCode -> String
$cshow :: CheckEmailAddressVerificationCode -> String
showsPrec :: Int -> CheckEmailAddressVerificationCode -> ShowS
$cshowsPrec :: Int -> CheckEmailAddressVerificationCode -> ShowS
Show, CheckEmailAddressVerificationCode
-> CheckEmailAddressVerificationCode -> Bool
(CheckEmailAddressVerificationCode
 -> CheckEmailAddressVerificationCode -> Bool)
-> (CheckEmailAddressVerificationCode
    -> CheckEmailAddressVerificationCode -> Bool)
-> Eq CheckEmailAddressVerificationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckEmailAddressVerificationCode
-> CheckEmailAddressVerificationCode -> Bool
$c/= :: CheckEmailAddressVerificationCode
-> CheckEmailAddressVerificationCode -> Bool
== :: CheckEmailAddressVerificationCode
-> CheckEmailAddressVerificationCode -> Bool
$c== :: CheckEmailAddressVerificationCode
-> CheckEmailAddressVerificationCode -> Bool
Eq, (forall x.
 CheckEmailAddressVerificationCode
 -> Rep CheckEmailAddressVerificationCode x)
-> (forall x.
    Rep CheckEmailAddressVerificationCode x
    -> CheckEmailAddressVerificationCode)
-> Generic CheckEmailAddressVerificationCode
forall x.
Rep CheckEmailAddressVerificationCode x
-> CheckEmailAddressVerificationCode
forall x.
CheckEmailAddressVerificationCode
-> Rep CheckEmailAddressVerificationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckEmailAddressVerificationCode x
-> CheckEmailAddressVerificationCode
$cfrom :: forall x.
CheckEmailAddressVerificationCode
-> Rep CheckEmailAddressVerificationCode x
Generic)

-- | Parameter of Function getPassportAuthorizationForm
data GetPassportAuthorizationForm
  = -- | Returns a Telegram Passport authorization form for sharing data with a service
    GetPassportAuthorizationForm
      { -- | User identifier of the service's bot
        GetPassportAuthorizationForm -> Int
bot_user_id :: I32,
        -- | Telegram Passport element types requested by the service
        GetPassportAuthorizationForm -> T
scope :: T,
        -- | Service's public_key
        GetPassportAuthorizationForm -> T
public_key :: T,
        -- | Authorization form nonce provided by the service
        GetPassportAuthorizationForm -> T
nonce :: T
      }
  deriving (Int -> GetPassportAuthorizationForm -> ShowS
[GetPassportAuthorizationForm] -> ShowS
GetPassportAuthorizationForm -> String
(Int -> GetPassportAuthorizationForm -> ShowS)
-> (GetPassportAuthorizationForm -> String)
-> ([GetPassportAuthorizationForm] -> ShowS)
-> Show GetPassportAuthorizationForm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPassportAuthorizationForm] -> ShowS
$cshowList :: [GetPassportAuthorizationForm] -> ShowS
show :: GetPassportAuthorizationForm -> String
$cshow :: GetPassportAuthorizationForm -> String
showsPrec :: Int -> GetPassportAuthorizationForm -> ShowS
$cshowsPrec :: Int -> GetPassportAuthorizationForm -> ShowS
Show, GetPassportAuthorizationForm
-> GetPassportAuthorizationForm -> Bool
(GetPassportAuthorizationForm
 -> GetPassportAuthorizationForm -> Bool)
-> (GetPassportAuthorizationForm
    -> GetPassportAuthorizationForm -> Bool)
-> Eq GetPassportAuthorizationForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPassportAuthorizationForm
-> GetPassportAuthorizationForm -> Bool
$c/= :: GetPassportAuthorizationForm
-> GetPassportAuthorizationForm -> Bool
== :: GetPassportAuthorizationForm
-> GetPassportAuthorizationForm -> Bool
$c== :: GetPassportAuthorizationForm
-> GetPassportAuthorizationForm -> Bool
Eq, (forall x.
 GetPassportAuthorizationForm -> Rep GetPassportAuthorizationForm x)
-> (forall x.
    Rep GetPassportAuthorizationForm x -> GetPassportAuthorizationForm)
-> Generic GetPassportAuthorizationForm
forall x.
Rep GetPassportAuthorizationForm x -> GetPassportAuthorizationForm
forall x.
GetPassportAuthorizationForm -> Rep GetPassportAuthorizationForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPassportAuthorizationForm x -> GetPassportAuthorizationForm
$cfrom :: forall x.
GetPassportAuthorizationForm -> Rep GetPassportAuthorizationForm x
Generic)

-- | Parameter of Function getPassportAuthorizationFormAvailableElements
data GetPassportAuthorizationFormAvailableElements
  = -- | Returns already available Telegram Passport elements suitable for completing a Telegram Passport authorization form. Result can be received only once for each authorization form
    GetPassportAuthorizationFormAvailableElements
      { -- | Authorization form identifier
        GetPassportAuthorizationFormAvailableElements -> Int
autorization_form_id :: I32,
        -- | Password of the current user
        GetPassportAuthorizationFormAvailableElements -> T
password :: T
      }
  deriving (Int -> GetPassportAuthorizationFormAvailableElements -> ShowS
[GetPassportAuthorizationFormAvailableElements] -> ShowS
GetPassportAuthorizationFormAvailableElements -> String
(Int -> GetPassportAuthorizationFormAvailableElements -> ShowS)
-> (GetPassportAuthorizationFormAvailableElements -> String)
-> ([GetPassportAuthorizationFormAvailableElements] -> ShowS)
-> Show GetPassportAuthorizationFormAvailableElements
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetPassportAuthorizationFormAvailableElements] -> ShowS
$cshowList :: [GetPassportAuthorizationFormAvailableElements] -> ShowS
show :: GetPassportAuthorizationFormAvailableElements -> String
$cshow :: GetPassportAuthorizationFormAvailableElements -> String
showsPrec :: Int -> GetPassportAuthorizationFormAvailableElements -> ShowS
$cshowsPrec :: Int -> GetPassportAuthorizationFormAvailableElements -> ShowS
Show, GetPassportAuthorizationFormAvailableElements
-> GetPassportAuthorizationFormAvailableElements -> Bool
(GetPassportAuthorizationFormAvailableElements
 -> GetPassportAuthorizationFormAvailableElements -> Bool)
-> (GetPassportAuthorizationFormAvailableElements
    -> GetPassportAuthorizationFormAvailableElements -> Bool)
-> Eq GetPassportAuthorizationFormAvailableElements
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetPassportAuthorizationFormAvailableElements
-> GetPassportAuthorizationFormAvailableElements -> Bool
$c/= :: GetPassportAuthorizationFormAvailableElements
-> GetPassportAuthorizationFormAvailableElements -> Bool
== :: GetPassportAuthorizationFormAvailableElements
-> GetPassportAuthorizationFormAvailableElements -> Bool
$c== :: GetPassportAuthorizationFormAvailableElements
-> GetPassportAuthorizationFormAvailableElements -> Bool
Eq, (forall x.
 GetPassportAuthorizationFormAvailableElements
 -> Rep GetPassportAuthorizationFormAvailableElements x)
-> (forall x.
    Rep GetPassportAuthorizationFormAvailableElements x
    -> GetPassportAuthorizationFormAvailableElements)
-> Generic GetPassportAuthorizationFormAvailableElements
forall x.
Rep GetPassportAuthorizationFormAvailableElements x
-> GetPassportAuthorizationFormAvailableElements
forall x.
GetPassportAuthorizationFormAvailableElements
-> Rep GetPassportAuthorizationFormAvailableElements x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetPassportAuthorizationFormAvailableElements x
-> GetPassportAuthorizationFormAvailableElements
$cfrom :: forall x.
GetPassportAuthorizationFormAvailableElements
-> Rep GetPassportAuthorizationFormAvailableElements x
Generic)

-- | Parameter of Function sendPassportAuthorizationForm
data SendPassportAuthorizationForm
  = -- | Sends a Telegram Passport authorization form, effectively sharing data with the service. This method must be called after getPassportAuthorizationFormAvailableElements if some previously available elements need to be used
    SendPassportAuthorizationForm
      { -- | Authorization form identifier
        SendPassportAuthorizationForm -> Int
autorization_form_id :: I32,
        -- | Types of Telegram Passport elements chosen by user to complete the authorization form
        SendPassportAuthorizationForm -> [PassportElementType]
types :: ([]) (PassportElementType)
      }
  deriving (Int -> SendPassportAuthorizationForm -> ShowS
[SendPassportAuthorizationForm] -> ShowS
SendPassportAuthorizationForm -> String
(Int -> SendPassportAuthorizationForm -> ShowS)
-> (SendPassportAuthorizationForm -> String)
-> ([SendPassportAuthorizationForm] -> ShowS)
-> Show SendPassportAuthorizationForm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendPassportAuthorizationForm] -> ShowS
$cshowList :: [SendPassportAuthorizationForm] -> ShowS
show :: SendPassportAuthorizationForm -> String
$cshow :: SendPassportAuthorizationForm -> String
showsPrec :: Int -> SendPassportAuthorizationForm -> ShowS
$cshowsPrec :: Int -> SendPassportAuthorizationForm -> ShowS
Show, SendPassportAuthorizationForm
-> SendPassportAuthorizationForm -> Bool
(SendPassportAuthorizationForm
 -> SendPassportAuthorizationForm -> Bool)
-> (SendPassportAuthorizationForm
    -> SendPassportAuthorizationForm -> Bool)
-> Eq SendPassportAuthorizationForm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendPassportAuthorizationForm
-> SendPassportAuthorizationForm -> Bool
$c/= :: SendPassportAuthorizationForm
-> SendPassportAuthorizationForm -> Bool
== :: SendPassportAuthorizationForm
-> SendPassportAuthorizationForm -> Bool
$c== :: SendPassportAuthorizationForm
-> SendPassportAuthorizationForm -> Bool
Eq, (forall x.
 SendPassportAuthorizationForm
 -> Rep SendPassportAuthorizationForm x)
-> (forall x.
    Rep SendPassportAuthorizationForm x
    -> SendPassportAuthorizationForm)
-> Generic SendPassportAuthorizationForm
forall x.
Rep SendPassportAuthorizationForm x
-> SendPassportAuthorizationForm
forall x.
SendPassportAuthorizationForm
-> Rep SendPassportAuthorizationForm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendPassportAuthorizationForm x
-> SendPassportAuthorizationForm
$cfrom :: forall x.
SendPassportAuthorizationForm
-> Rep SendPassportAuthorizationForm x
Generic)

-- | Parameter of Function sendPhoneNumberConfirmationCode
data SendPhoneNumberConfirmationCode
  = -- | Sends phone number confirmation code. Should be called when user presses "https://t.me/confirmphone?phone=*******&hash=**********" or "tg://confirmphone?phone=*******&hash=**********" link
    SendPhoneNumberConfirmationCode
      { -- | Value of the "hash" parameter from the link
        SendPhoneNumberConfirmationCode -> T
hash :: T,
        -- | Value of the "phone" parameter from the link
        SendPhoneNumberConfirmationCode -> T
phone_number :: T,
        -- | Settings for the authentication of the user's phone number
        SendPhoneNumberConfirmationCode
-> PhoneNumberAuthenticationSettings
settings :: PhoneNumberAuthenticationSettings
      }
  deriving (Int -> SendPhoneNumberConfirmationCode -> ShowS
[SendPhoneNumberConfirmationCode] -> ShowS
SendPhoneNumberConfirmationCode -> String
(Int -> SendPhoneNumberConfirmationCode -> ShowS)
-> (SendPhoneNumberConfirmationCode -> String)
-> ([SendPhoneNumberConfirmationCode] -> ShowS)
-> Show SendPhoneNumberConfirmationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendPhoneNumberConfirmationCode] -> ShowS
$cshowList :: [SendPhoneNumberConfirmationCode] -> ShowS
show :: SendPhoneNumberConfirmationCode -> String
$cshow :: SendPhoneNumberConfirmationCode -> String
showsPrec :: Int -> SendPhoneNumberConfirmationCode -> ShowS
$cshowsPrec :: Int -> SendPhoneNumberConfirmationCode -> ShowS
Show, SendPhoneNumberConfirmationCode
-> SendPhoneNumberConfirmationCode -> Bool
(SendPhoneNumberConfirmationCode
 -> SendPhoneNumberConfirmationCode -> Bool)
-> (SendPhoneNumberConfirmationCode
    -> SendPhoneNumberConfirmationCode -> Bool)
-> Eq SendPhoneNumberConfirmationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendPhoneNumberConfirmationCode
-> SendPhoneNumberConfirmationCode -> Bool
$c/= :: SendPhoneNumberConfirmationCode
-> SendPhoneNumberConfirmationCode -> Bool
== :: SendPhoneNumberConfirmationCode
-> SendPhoneNumberConfirmationCode -> Bool
$c== :: SendPhoneNumberConfirmationCode
-> SendPhoneNumberConfirmationCode -> Bool
Eq, (forall x.
 SendPhoneNumberConfirmationCode
 -> Rep SendPhoneNumberConfirmationCode x)
-> (forall x.
    Rep SendPhoneNumberConfirmationCode x
    -> SendPhoneNumberConfirmationCode)
-> Generic SendPhoneNumberConfirmationCode
forall x.
Rep SendPhoneNumberConfirmationCode x
-> SendPhoneNumberConfirmationCode
forall x.
SendPhoneNumberConfirmationCode
-> Rep SendPhoneNumberConfirmationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SendPhoneNumberConfirmationCode x
-> SendPhoneNumberConfirmationCode
$cfrom :: forall x.
SendPhoneNumberConfirmationCode
-> Rep SendPhoneNumberConfirmationCode x
Generic)

-- | Parameter of Function resendPhoneNumberConfirmationCode
data ResendPhoneNumberConfirmationCode
  = -- | Resends phone number confirmation code
    ResendPhoneNumberConfirmationCode
      {
      }
  deriving (Int -> ResendPhoneNumberConfirmationCode -> ShowS
[ResendPhoneNumberConfirmationCode] -> ShowS
ResendPhoneNumberConfirmationCode -> String
(Int -> ResendPhoneNumberConfirmationCode -> ShowS)
-> (ResendPhoneNumberConfirmationCode -> String)
-> ([ResendPhoneNumberConfirmationCode] -> ShowS)
-> Show ResendPhoneNumberConfirmationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ResendPhoneNumberConfirmationCode] -> ShowS
$cshowList :: [ResendPhoneNumberConfirmationCode] -> ShowS
show :: ResendPhoneNumberConfirmationCode -> String
$cshow :: ResendPhoneNumberConfirmationCode -> String
showsPrec :: Int -> ResendPhoneNumberConfirmationCode -> ShowS
$cshowsPrec :: Int -> ResendPhoneNumberConfirmationCode -> ShowS
Show, ResendPhoneNumberConfirmationCode
-> ResendPhoneNumberConfirmationCode -> Bool
(ResendPhoneNumberConfirmationCode
 -> ResendPhoneNumberConfirmationCode -> Bool)
-> (ResendPhoneNumberConfirmationCode
    -> ResendPhoneNumberConfirmationCode -> Bool)
-> Eq ResendPhoneNumberConfirmationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ResendPhoneNumberConfirmationCode
-> ResendPhoneNumberConfirmationCode -> Bool
$c/= :: ResendPhoneNumberConfirmationCode
-> ResendPhoneNumberConfirmationCode -> Bool
== :: ResendPhoneNumberConfirmationCode
-> ResendPhoneNumberConfirmationCode -> Bool
$c== :: ResendPhoneNumberConfirmationCode
-> ResendPhoneNumberConfirmationCode -> Bool
Eq, (forall x.
 ResendPhoneNumberConfirmationCode
 -> Rep ResendPhoneNumberConfirmationCode x)
-> (forall x.
    Rep ResendPhoneNumberConfirmationCode x
    -> ResendPhoneNumberConfirmationCode)
-> Generic ResendPhoneNumberConfirmationCode
forall x.
Rep ResendPhoneNumberConfirmationCode x
-> ResendPhoneNumberConfirmationCode
forall x.
ResendPhoneNumberConfirmationCode
-> Rep ResendPhoneNumberConfirmationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ResendPhoneNumberConfirmationCode x
-> ResendPhoneNumberConfirmationCode
$cfrom :: forall x.
ResendPhoneNumberConfirmationCode
-> Rep ResendPhoneNumberConfirmationCode x
Generic)

-- | Parameter of Function checkPhoneNumberConfirmationCode
data CheckPhoneNumberConfirmationCode
  = -- | Checks phone number confirmation code
    CheckPhoneNumberConfirmationCode
      { -- | The phone number confirmation code
        CheckPhoneNumberConfirmationCode -> T
code :: T
      }
  deriving (Int -> CheckPhoneNumberConfirmationCode -> ShowS
[CheckPhoneNumberConfirmationCode] -> ShowS
CheckPhoneNumberConfirmationCode -> String
(Int -> CheckPhoneNumberConfirmationCode -> ShowS)
-> (CheckPhoneNumberConfirmationCode -> String)
-> ([CheckPhoneNumberConfirmationCode] -> ShowS)
-> Show CheckPhoneNumberConfirmationCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CheckPhoneNumberConfirmationCode] -> ShowS
$cshowList :: [CheckPhoneNumberConfirmationCode] -> ShowS
show :: CheckPhoneNumberConfirmationCode -> String
$cshow :: CheckPhoneNumberConfirmationCode -> String
showsPrec :: Int -> CheckPhoneNumberConfirmationCode -> ShowS
$cshowsPrec :: Int -> CheckPhoneNumberConfirmationCode -> ShowS
Show, CheckPhoneNumberConfirmationCode
-> CheckPhoneNumberConfirmationCode -> Bool
(CheckPhoneNumberConfirmationCode
 -> CheckPhoneNumberConfirmationCode -> Bool)
-> (CheckPhoneNumberConfirmationCode
    -> CheckPhoneNumberConfirmationCode -> Bool)
-> Eq CheckPhoneNumberConfirmationCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CheckPhoneNumberConfirmationCode
-> CheckPhoneNumberConfirmationCode -> Bool
$c/= :: CheckPhoneNumberConfirmationCode
-> CheckPhoneNumberConfirmationCode -> Bool
== :: CheckPhoneNumberConfirmationCode
-> CheckPhoneNumberConfirmationCode -> Bool
$c== :: CheckPhoneNumberConfirmationCode
-> CheckPhoneNumberConfirmationCode -> Bool
Eq, (forall x.
 CheckPhoneNumberConfirmationCode
 -> Rep CheckPhoneNumberConfirmationCode x)
-> (forall x.
    Rep CheckPhoneNumberConfirmationCode x
    -> CheckPhoneNumberConfirmationCode)
-> Generic CheckPhoneNumberConfirmationCode
forall x.
Rep CheckPhoneNumberConfirmationCode x
-> CheckPhoneNumberConfirmationCode
forall x.
CheckPhoneNumberConfirmationCode
-> Rep CheckPhoneNumberConfirmationCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CheckPhoneNumberConfirmationCode x
-> CheckPhoneNumberConfirmationCode
$cfrom :: forall x.
CheckPhoneNumberConfirmationCode
-> Rep CheckPhoneNumberConfirmationCode x
Generic)

-- | Parameter of Function setBotUpdatesStatus
data SetBotUpdatesStatus
  = -- | Informs the server about the number of pending bot updates if they haven't been processed for a long time; for bots only
    SetBotUpdatesStatus
      { -- | The number of pending updates
        SetBotUpdatesStatus -> Int
pending_update_count :: I32,
        -- | The last error message
        SetBotUpdatesStatus -> T
error_message :: T
      }
  deriving (Int -> SetBotUpdatesStatus -> ShowS
[SetBotUpdatesStatus] -> ShowS
SetBotUpdatesStatus -> String
(Int -> SetBotUpdatesStatus -> ShowS)
-> (SetBotUpdatesStatus -> String)
-> ([SetBotUpdatesStatus] -> ShowS)
-> Show SetBotUpdatesStatus
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetBotUpdatesStatus] -> ShowS
$cshowList :: [SetBotUpdatesStatus] -> ShowS
show :: SetBotUpdatesStatus -> String
$cshow :: SetBotUpdatesStatus -> String
showsPrec :: Int -> SetBotUpdatesStatus -> ShowS
$cshowsPrec :: Int -> SetBotUpdatesStatus -> ShowS
Show, SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool
(SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool)
-> (SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool)
-> Eq SetBotUpdatesStatus
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool
$c/= :: SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool
== :: SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool
$c== :: SetBotUpdatesStatus -> SetBotUpdatesStatus -> Bool
Eq, (forall x. SetBotUpdatesStatus -> Rep SetBotUpdatesStatus x)
-> (forall x. Rep SetBotUpdatesStatus x -> SetBotUpdatesStatus)
-> Generic SetBotUpdatesStatus
forall x. Rep SetBotUpdatesStatus x -> SetBotUpdatesStatus
forall x. SetBotUpdatesStatus -> Rep SetBotUpdatesStatus x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetBotUpdatesStatus x -> SetBotUpdatesStatus
$cfrom :: forall x. SetBotUpdatesStatus -> Rep SetBotUpdatesStatus x
Generic)

-- | Parameter of Function uploadStickerFile
data UploadStickerFile
  = -- | Uploads a PNG image with a sticker; for bots only; returns the uploaded file
    UploadStickerFile
      { -- | Sticker file owner
        UploadStickerFile -> Int
user_id :: I32,
        -- | PNG image with the sticker; must be up to 512 KB in size and fit in 512x512 square
        UploadStickerFile -> InputFile
png_sticker :: InputFile
      }
  deriving (Int -> UploadStickerFile -> ShowS
[UploadStickerFile] -> ShowS
UploadStickerFile -> String
(Int -> UploadStickerFile -> ShowS)
-> (UploadStickerFile -> String)
-> ([UploadStickerFile] -> ShowS)
-> Show UploadStickerFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadStickerFile] -> ShowS
$cshowList :: [UploadStickerFile] -> ShowS
show :: UploadStickerFile -> String
$cshow :: UploadStickerFile -> String
showsPrec :: Int -> UploadStickerFile -> ShowS
$cshowsPrec :: Int -> UploadStickerFile -> ShowS
Show, UploadStickerFile -> UploadStickerFile -> Bool
(UploadStickerFile -> UploadStickerFile -> Bool)
-> (UploadStickerFile -> UploadStickerFile -> Bool)
-> Eq UploadStickerFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadStickerFile -> UploadStickerFile -> Bool
$c/= :: UploadStickerFile -> UploadStickerFile -> Bool
== :: UploadStickerFile -> UploadStickerFile -> Bool
$c== :: UploadStickerFile -> UploadStickerFile -> Bool
Eq, (forall x. UploadStickerFile -> Rep UploadStickerFile x)
-> (forall x. Rep UploadStickerFile x -> UploadStickerFile)
-> Generic UploadStickerFile
forall x. Rep UploadStickerFile x -> UploadStickerFile
forall x. UploadStickerFile -> Rep UploadStickerFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UploadStickerFile x -> UploadStickerFile
$cfrom :: forall x. UploadStickerFile -> Rep UploadStickerFile x
Generic)

-- | Parameter of Function createNewStickerSet
data CreateNewStickerSet
  = -- | Creates a new sticker set; for bots only. Returns the newly created sticker set
    CreateNewStickerSet
      { -- | Sticker set owner
        CreateNewStickerSet -> Int
user_id :: I32,
        -- | Sticker set title; 1-64 characters
        CreateNewStickerSet -> T
title :: T,
        -- | Sticker set name. Can contain only English letters, digits and underscores. Must end with *"_by_<bot username>"* (*<bot_username>* is case insensitive); 1-64 characters
        CreateNewStickerSet -> T
name :: T,
        -- | True, if stickers are masks. Animated stickers can't be masks
        CreateNewStickerSet -> Bool
is_masks :: Bool,
        -- | List of stickers to be added to the set; must be non-empty. All stickers must be of the same type
        CreateNewStickerSet -> [InputSticker]
stickers :: ([]) (InputSticker)
      }
  deriving (Int -> CreateNewStickerSet -> ShowS
[CreateNewStickerSet] -> ShowS
CreateNewStickerSet -> String
(Int -> CreateNewStickerSet -> ShowS)
-> (CreateNewStickerSet -> String)
-> ([CreateNewStickerSet] -> ShowS)
-> Show CreateNewStickerSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateNewStickerSet] -> ShowS
$cshowList :: [CreateNewStickerSet] -> ShowS
show :: CreateNewStickerSet -> String
$cshow :: CreateNewStickerSet -> String
showsPrec :: Int -> CreateNewStickerSet -> ShowS
$cshowsPrec :: Int -> CreateNewStickerSet -> ShowS
Show, CreateNewStickerSet -> CreateNewStickerSet -> Bool
(CreateNewStickerSet -> CreateNewStickerSet -> Bool)
-> (CreateNewStickerSet -> CreateNewStickerSet -> Bool)
-> Eq CreateNewStickerSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateNewStickerSet -> CreateNewStickerSet -> Bool
$c/= :: CreateNewStickerSet -> CreateNewStickerSet -> Bool
== :: CreateNewStickerSet -> CreateNewStickerSet -> Bool
$c== :: CreateNewStickerSet -> CreateNewStickerSet -> Bool
Eq, (forall x. CreateNewStickerSet -> Rep CreateNewStickerSet x)
-> (forall x. Rep CreateNewStickerSet x -> CreateNewStickerSet)
-> Generic CreateNewStickerSet
forall x. Rep CreateNewStickerSet x -> CreateNewStickerSet
forall x. CreateNewStickerSet -> Rep CreateNewStickerSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateNewStickerSet x -> CreateNewStickerSet
$cfrom :: forall x. CreateNewStickerSet -> Rep CreateNewStickerSet x
Generic)

-- | Parameter of Function addStickerToSet
data AddStickerToSet
  = -- | Adds a new sticker to a set; for bots only. Returns the sticker set
    AddStickerToSet
      { -- | Sticker set owner
        AddStickerToSet -> Int
user_id :: I32,
        -- | Sticker set name
        AddStickerToSet -> T
name :: T,
        -- | Sticker to add to the set
        AddStickerToSet -> InputSticker
sticker :: InputSticker
      }
  deriving (Int -> AddStickerToSet -> ShowS
[AddStickerToSet] -> ShowS
AddStickerToSet -> String
(Int -> AddStickerToSet -> ShowS)
-> (AddStickerToSet -> String)
-> ([AddStickerToSet] -> ShowS)
-> Show AddStickerToSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddStickerToSet] -> ShowS
$cshowList :: [AddStickerToSet] -> ShowS
show :: AddStickerToSet -> String
$cshow :: AddStickerToSet -> String
showsPrec :: Int -> AddStickerToSet -> ShowS
$cshowsPrec :: Int -> AddStickerToSet -> ShowS
Show, AddStickerToSet -> AddStickerToSet -> Bool
(AddStickerToSet -> AddStickerToSet -> Bool)
-> (AddStickerToSet -> AddStickerToSet -> Bool)
-> Eq AddStickerToSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddStickerToSet -> AddStickerToSet -> Bool
$c/= :: AddStickerToSet -> AddStickerToSet -> Bool
== :: AddStickerToSet -> AddStickerToSet -> Bool
$c== :: AddStickerToSet -> AddStickerToSet -> Bool
Eq, (forall x. AddStickerToSet -> Rep AddStickerToSet x)
-> (forall x. Rep AddStickerToSet x -> AddStickerToSet)
-> Generic AddStickerToSet
forall x. Rep AddStickerToSet x -> AddStickerToSet
forall x. AddStickerToSet -> Rep AddStickerToSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddStickerToSet x -> AddStickerToSet
$cfrom :: forall x. AddStickerToSet -> Rep AddStickerToSet x
Generic)

-- | Parameter of Function setStickerSetThumbnail
data SetStickerSetThumbnail
  = -- | Sets a sticker set thumbnail; for bots only. Returns the sticker set
    SetStickerSetThumbnail
      { -- | Sticker set owner
        SetStickerSetThumbnail -> Int
user_id :: I32,
        -- | Sticker set name
        SetStickerSetThumbnail -> T
name :: T,
        -- | Thumbnail to set in PNG or TGS format. Animated thumbnail must be set for animated sticker sets and only for them. You can use a zero InputFileId to delete the thumbnail
        SetStickerSetThumbnail -> InputFile
thumbnail :: InputFile
      }
  deriving (Int -> SetStickerSetThumbnail -> ShowS
[SetStickerSetThumbnail] -> ShowS
SetStickerSetThumbnail -> String
(Int -> SetStickerSetThumbnail -> ShowS)
-> (SetStickerSetThumbnail -> String)
-> ([SetStickerSetThumbnail] -> ShowS)
-> Show SetStickerSetThumbnail
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetStickerSetThumbnail] -> ShowS
$cshowList :: [SetStickerSetThumbnail] -> ShowS
show :: SetStickerSetThumbnail -> String
$cshow :: SetStickerSetThumbnail -> String
showsPrec :: Int -> SetStickerSetThumbnail -> ShowS
$cshowsPrec :: Int -> SetStickerSetThumbnail -> ShowS
Show, SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool
(SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool)
-> (SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool)
-> Eq SetStickerSetThumbnail
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool
$c/= :: SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool
== :: SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool
$c== :: SetStickerSetThumbnail -> SetStickerSetThumbnail -> Bool
Eq, (forall x. SetStickerSetThumbnail -> Rep SetStickerSetThumbnail x)
-> (forall x.
    Rep SetStickerSetThumbnail x -> SetStickerSetThumbnail)
-> Generic SetStickerSetThumbnail
forall x. Rep SetStickerSetThumbnail x -> SetStickerSetThumbnail
forall x. SetStickerSetThumbnail -> Rep SetStickerSetThumbnail x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetStickerSetThumbnail x -> SetStickerSetThumbnail
$cfrom :: forall x. SetStickerSetThumbnail -> Rep SetStickerSetThumbnail x
Generic)

-- | Parameter of Function setStickerPositionInSet
data SetStickerPositionInSet
  = -- | Changes the position of a sticker in the set to which it belongs; for bots only. The sticker set must have been created by the bot
    SetStickerPositionInSet
      { -- | Sticker
        SetStickerPositionInSet -> InputFile
sticker :: InputFile,
        -- | New position of the sticker in the set, zero-based
        SetStickerPositionInSet -> Int
position :: I32
      }
  deriving (Int -> SetStickerPositionInSet -> ShowS
[SetStickerPositionInSet] -> ShowS
SetStickerPositionInSet -> String
(Int -> SetStickerPositionInSet -> ShowS)
-> (SetStickerPositionInSet -> String)
-> ([SetStickerPositionInSet] -> ShowS)
-> Show SetStickerPositionInSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetStickerPositionInSet] -> ShowS
$cshowList :: [SetStickerPositionInSet] -> ShowS
show :: SetStickerPositionInSet -> String
$cshow :: SetStickerPositionInSet -> String
showsPrec :: Int -> SetStickerPositionInSet -> ShowS
$cshowsPrec :: Int -> SetStickerPositionInSet -> ShowS
Show, SetStickerPositionInSet -> SetStickerPositionInSet -> Bool
(SetStickerPositionInSet -> SetStickerPositionInSet -> Bool)
-> (SetStickerPositionInSet -> SetStickerPositionInSet -> Bool)
-> Eq SetStickerPositionInSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetStickerPositionInSet -> SetStickerPositionInSet -> Bool
$c/= :: SetStickerPositionInSet -> SetStickerPositionInSet -> Bool
== :: SetStickerPositionInSet -> SetStickerPositionInSet -> Bool
$c== :: SetStickerPositionInSet -> SetStickerPositionInSet -> Bool
Eq, (forall x.
 SetStickerPositionInSet -> Rep SetStickerPositionInSet x)
-> (forall x.
    Rep SetStickerPositionInSet x -> SetStickerPositionInSet)
-> Generic SetStickerPositionInSet
forall x. Rep SetStickerPositionInSet x -> SetStickerPositionInSet
forall x. SetStickerPositionInSet -> Rep SetStickerPositionInSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetStickerPositionInSet x -> SetStickerPositionInSet
$cfrom :: forall x. SetStickerPositionInSet -> Rep SetStickerPositionInSet x
Generic)

-- | Parameter of Function removeStickerFromSet
data RemoveStickerFromSet
  = -- | Removes a sticker from the set to which it belongs; for bots only. The sticker set must have been created by the bot
    RemoveStickerFromSet
      { -- | Sticker
        RemoveStickerFromSet -> InputFile
sticker :: InputFile
      }
  deriving (Int -> RemoveStickerFromSet -> ShowS
[RemoveStickerFromSet] -> ShowS
RemoveStickerFromSet -> String
(Int -> RemoveStickerFromSet -> ShowS)
-> (RemoveStickerFromSet -> String)
-> ([RemoveStickerFromSet] -> ShowS)
-> Show RemoveStickerFromSet
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveStickerFromSet] -> ShowS
$cshowList :: [RemoveStickerFromSet] -> ShowS
show :: RemoveStickerFromSet -> String
$cshow :: RemoveStickerFromSet -> String
showsPrec :: Int -> RemoveStickerFromSet -> ShowS
$cshowsPrec :: Int -> RemoveStickerFromSet -> ShowS
Show, RemoveStickerFromSet -> RemoveStickerFromSet -> Bool
(RemoveStickerFromSet -> RemoveStickerFromSet -> Bool)
-> (RemoveStickerFromSet -> RemoveStickerFromSet -> Bool)
-> Eq RemoveStickerFromSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveStickerFromSet -> RemoveStickerFromSet -> Bool
$c/= :: RemoveStickerFromSet -> RemoveStickerFromSet -> Bool
== :: RemoveStickerFromSet -> RemoveStickerFromSet -> Bool
$c== :: RemoveStickerFromSet -> RemoveStickerFromSet -> Bool
Eq, (forall x. RemoveStickerFromSet -> Rep RemoveStickerFromSet x)
-> (forall x. Rep RemoveStickerFromSet x -> RemoveStickerFromSet)
-> Generic RemoveStickerFromSet
forall x. Rep RemoveStickerFromSet x -> RemoveStickerFromSet
forall x. RemoveStickerFromSet -> Rep RemoveStickerFromSet x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveStickerFromSet x -> RemoveStickerFromSet
$cfrom :: forall x. RemoveStickerFromSet -> Rep RemoveStickerFromSet x
Generic)

-- | Parameter of Function getMapThumbnailFile
data GetMapThumbnailFile
  = -- | Returns information about a file with a map thumbnail in PNG format. Only map thumbnail files with size less than 1MB can be downloaded
    GetMapThumbnailFile
      { -- | Location of the map center
        GetMapThumbnailFile -> Location
location :: Location,
        -- | Map zoom level; 13-20
        GetMapThumbnailFile -> Int
zoom :: I32,
        -- | Map width in pixels before applying scale; 16-1024
        GetMapThumbnailFile -> Int
width :: I32,
        -- | Map height in pixels before applying scale; 16-1024
        GetMapThumbnailFile -> Int
height :: I32,
        -- | Map scale; 1-3
        GetMapThumbnailFile -> Int
scale :: I32,
        -- | Identifier of a chat, in which the thumbnail will be shown. Use 0 if unknown
        GetMapThumbnailFile -> Int
chat_id :: I53
      }
  deriving (Int -> GetMapThumbnailFile -> ShowS
[GetMapThumbnailFile] -> ShowS
GetMapThumbnailFile -> String
(Int -> GetMapThumbnailFile -> ShowS)
-> (GetMapThumbnailFile -> String)
-> ([GetMapThumbnailFile] -> ShowS)
-> Show GetMapThumbnailFile
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetMapThumbnailFile] -> ShowS
$cshowList :: [GetMapThumbnailFile] -> ShowS
show :: GetMapThumbnailFile -> String
$cshow :: GetMapThumbnailFile -> String
showsPrec :: Int -> GetMapThumbnailFile -> ShowS
$cshowsPrec :: Int -> GetMapThumbnailFile -> ShowS
Show, GetMapThumbnailFile -> GetMapThumbnailFile -> Bool
(GetMapThumbnailFile -> GetMapThumbnailFile -> Bool)
-> (GetMapThumbnailFile -> GetMapThumbnailFile -> Bool)
-> Eq GetMapThumbnailFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetMapThumbnailFile -> GetMapThumbnailFile -> Bool
$c/= :: GetMapThumbnailFile -> GetMapThumbnailFile -> Bool
== :: GetMapThumbnailFile -> GetMapThumbnailFile -> Bool
$c== :: GetMapThumbnailFile -> GetMapThumbnailFile -> Bool
Eq, (forall x. GetMapThumbnailFile -> Rep GetMapThumbnailFile x)
-> (forall x. Rep GetMapThumbnailFile x -> GetMapThumbnailFile)
-> Generic GetMapThumbnailFile
forall x. Rep GetMapThumbnailFile x -> GetMapThumbnailFile
forall x. GetMapThumbnailFile -> Rep GetMapThumbnailFile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetMapThumbnailFile x -> GetMapThumbnailFile
$cfrom :: forall x. GetMapThumbnailFile -> Rep GetMapThumbnailFile x
Generic)

-- | Parameter of Function acceptTermsOfService
data AcceptTermsOfService
  = -- | Accepts Telegram terms of services
    AcceptTermsOfService
      { -- | Terms of service identifier
        AcceptTermsOfService -> T
terms_of_service_id :: T
      }
  deriving (Int -> AcceptTermsOfService -> ShowS
[AcceptTermsOfService] -> ShowS
AcceptTermsOfService -> String
(Int -> AcceptTermsOfService -> ShowS)
-> (AcceptTermsOfService -> String)
-> ([AcceptTermsOfService] -> ShowS)
-> Show AcceptTermsOfService
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AcceptTermsOfService] -> ShowS
$cshowList :: [AcceptTermsOfService] -> ShowS
show :: AcceptTermsOfService -> String
$cshow :: AcceptTermsOfService -> String
showsPrec :: Int -> AcceptTermsOfService -> ShowS
$cshowsPrec :: Int -> AcceptTermsOfService -> ShowS
Show, AcceptTermsOfService -> AcceptTermsOfService -> Bool
(AcceptTermsOfService -> AcceptTermsOfService -> Bool)
-> (AcceptTermsOfService -> AcceptTermsOfService -> Bool)
-> Eq AcceptTermsOfService
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AcceptTermsOfService -> AcceptTermsOfService -> Bool
$c/= :: AcceptTermsOfService -> AcceptTermsOfService -> Bool
== :: AcceptTermsOfService -> AcceptTermsOfService -> Bool
$c== :: AcceptTermsOfService -> AcceptTermsOfService -> Bool
Eq, (forall x. AcceptTermsOfService -> Rep AcceptTermsOfService x)
-> (forall x. Rep AcceptTermsOfService x -> AcceptTermsOfService)
-> Generic AcceptTermsOfService
forall x. Rep AcceptTermsOfService x -> AcceptTermsOfService
forall x. AcceptTermsOfService -> Rep AcceptTermsOfService x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AcceptTermsOfService x -> AcceptTermsOfService
$cfrom :: forall x. AcceptTermsOfService -> Rep AcceptTermsOfService x
Generic)

-- | Parameter of Function sendCustomRequest
data SendCustomRequest
  = -- | Sends a custom request; for bots only
    SendCustomRequest
      { -- | The method name
        SendCustomRequest -> T
method :: T,
        -- | JSON-serialized method parameters
        SendCustomRequest -> T
parameters :: T
      }
  deriving (Int -> SendCustomRequest -> ShowS
[SendCustomRequest] -> ShowS
SendCustomRequest -> String
(Int -> SendCustomRequest -> ShowS)
-> (SendCustomRequest -> String)
-> ([SendCustomRequest] -> ShowS)
-> Show SendCustomRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SendCustomRequest] -> ShowS
$cshowList :: [SendCustomRequest] -> ShowS
show :: SendCustomRequest -> String
$cshow :: SendCustomRequest -> String
showsPrec :: Int -> SendCustomRequest -> ShowS
$cshowsPrec :: Int -> SendCustomRequest -> ShowS
Show, SendCustomRequest -> SendCustomRequest -> Bool
(SendCustomRequest -> SendCustomRequest -> Bool)
-> (SendCustomRequest -> SendCustomRequest -> Bool)
-> Eq SendCustomRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SendCustomRequest -> SendCustomRequest -> Bool
$c/= :: SendCustomRequest -> SendCustomRequest -> Bool
== :: SendCustomRequest -> SendCustomRequest -> Bool
$c== :: SendCustomRequest -> SendCustomRequest -> Bool
Eq, (forall x. SendCustomRequest -> Rep SendCustomRequest x)
-> (forall x. Rep SendCustomRequest x -> SendCustomRequest)
-> Generic SendCustomRequest
forall x. Rep SendCustomRequest x -> SendCustomRequest
forall x. SendCustomRequest -> Rep SendCustomRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SendCustomRequest x -> SendCustomRequest
$cfrom :: forall x. SendCustomRequest -> Rep SendCustomRequest x
Generic)

-- | Parameter of Function answerCustomQuery
data AnswerCustomQuery
  = -- | Answers a custom query; for bots only
    AnswerCustomQuery
      { -- | Identifier of a custom query
        AnswerCustomQuery -> I64
custom_query_id :: I64,
        -- | JSON-serialized answer to the query
        AnswerCustomQuery -> T
data_ :: T
      }
  deriving (Int -> AnswerCustomQuery -> ShowS
[AnswerCustomQuery] -> ShowS
AnswerCustomQuery -> String
(Int -> AnswerCustomQuery -> ShowS)
-> (AnswerCustomQuery -> String)
-> ([AnswerCustomQuery] -> ShowS)
-> Show AnswerCustomQuery
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AnswerCustomQuery] -> ShowS
$cshowList :: [AnswerCustomQuery] -> ShowS
show :: AnswerCustomQuery -> String
$cshow :: AnswerCustomQuery -> String
showsPrec :: Int -> AnswerCustomQuery -> ShowS
$cshowsPrec :: Int -> AnswerCustomQuery -> ShowS
Show, AnswerCustomQuery -> AnswerCustomQuery -> Bool
(AnswerCustomQuery -> AnswerCustomQuery -> Bool)
-> (AnswerCustomQuery -> AnswerCustomQuery -> Bool)
-> Eq AnswerCustomQuery
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AnswerCustomQuery -> AnswerCustomQuery -> Bool
$c/= :: AnswerCustomQuery -> AnswerCustomQuery -> Bool
== :: AnswerCustomQuery -> AnswerCustomQuery -> Bool
$c== :: AnswerCustomQuery -> AnswerCustomQuery -> Bool
Eq, (forall x. AnswerCustomQuery -> Rep AnswerCustomQuery x)
-> (forall x. Rep AnswerCustomQuery x -> AnswerCustomQuery)
-> Generic AnswerCustomQuery
forall x. Rep AnswerCustomQuery x -> AnswerCustomQuery
forall x. AnswerCustomQuery -> Rep AnswerCustomQuery x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AnswerCustomQuery x -> AnswerCustomQuery
$cfrom :: forall x. AnswerCustomQuery -> Rep AnswerCustomQuery x
Generic)

-- | Parameter of Function setAlarm
data SetAlarm
  = -- | Succeeds after a specified amount of time has passed. Can be called before authorization. Can be called before initialization
    SetAlarm
      { -- | Number of seconds before the function returns
        SetAlarm -> Double
seconds :: Double
      }
  deriving (Int -> SetAlarm -> ShowS
[SetAlarm] -> ShowS
SetAlarm -> String
(Int -> SetAlarm -> ShowS)
-> (SetAlarm -> String) -> ([SetAlarm] -> ShowS) -> Show SetAlarm
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetAlarm] -> ShowS
$cshowList :: [SetAlarm] -> ShowS
show :: SetAlarm -> String
$cshow :: SetAlarm -> String
showsPrec :: Int -> SetAlarm -> ShowS
$cshowsPrec :: Int -> SetAlarm -> ShowS
Show, SetAlarm -> SetAlarm -> Bool
(SetAlarm -> SetAlarm -> Bool)
-> (SetAlarm -> SetAlarm -> Bool) -> Eq SetAlarm
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetAlarm -> SetAlarm -> Bool
$c/= :: SetAlarm -> SetAlarm -> Bool
== :: SetAlarm -> SetAlarm -> Bool
$c== :: SetAlarm -> SetAlarm -> Bool
Eq, (forall x. SetAlarm -> Rep SetAlarm x)
-> (forall x. Rep SetAlarm x -> SetAlarm) -> Generic SetAlarm
forall x. Rep SetAlarm x -> SetAlarm
forall x. SetAlarm -> Rep SetAlarm x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetAlarm x -> SetAlarm
$cfrom :: forall x. SetAlarm -> Rep SetAlarm x
Generic)

-- | Parameter of Function getCountryCode
data GetCountryCode
  = -- | Uses current user IP address to found their country. Returns two-letter ISO 3166-1 alpha-2 country code. Can be called before authorization
    GetCountryCode
      {
      }
  deriving (Int -> GetCountryCode -> ShowS
[GetCountryCode] -> ShowS
GetCountryCode -> String
(Int -> GetCountryCode -> ShowS)
-> (GetCountryCode -> String)
-> ([GetCountryCode] -> ShowS)
-> Show GetCountryCode
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCountryCode] -> ShowS
$cshowList :: [GetCountryCode] -> ShowS
show :: GetCountryCode -> String
$cshow :: GetCountryCode -> String
showsPrec :: Int -> GetCountryCode -> ShowS
$cshowsPrec :: Int -> GetCountryCode -> ShowS
Show, GetCountryCode -> GetCountryCode -> Bool
(GetCountryCode -> GetCountryCode -> Bool)
-> (GetCountryCode -> GetCountryCode -> Bool) -> Eq GetCountryCode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCountryCode -> GetCountryCode -> Bool
$c/= :: GetCountryCode -> GetCountryCode -> Bool
== :: GetCountryCode -> GetCountryCode -> Bool
$c== :: GetCountryCode -> GetCountryCode -> Bool
Eq, (forall x. GetCountryCode -> Rep GetCountryCode x)
-> (forall x. Rep GetCountryCode x -> GetCountryCode)
-> Generic GetCountryCode
forall x. Rep GetCountryCode x -> GetCountryCode
forall x. GetCountryCode -> Rep GetCountryCode x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCountryCode x -> GetCountryCode
$cfrom :: forall x. GetCountryCode -> Rep GetCountryCode x
Generic)

-- | Parameter of Function getInviteText
data GetInviteText
  = -- | Returns the default text for invitation messages to be used as a placeholder when the current user invites friends to Telegram
    GetInviteText
      {
      }
  deriving (Int -> GetInviteText -> ShowS
[GetInviteText] -> ShowS
GetInviteText -> String
(Int -> GetInviteText -> ShowS)
-> (GetInviteText -> String)
-> ([GetInviteText] -> ShowS)
-> Show GetInviteText
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetInviteText] -> ShowS
$cshowList :: [GetInviteText] -> ShowS
show :: GetInviteText -> String
$cshow :: GetInviteText -> String
showsPrec :: Int -> GetInviteText -> ShowS
$cshowsPrec :: Int -> GetInviteText -> ShowS
Show, GetInviteText -> GetInviteText -> Bool
(GetInviteText -> GetInviteText -> Bool)
-> (GetInviteText -> GetInviteText -> Bool) -> Eq GetInviteText
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetInviteText -> GetInviteText -> Bool
$c/= :: GetInviteText -> GetInviteText -> Bool
== :: GetInviteText -> GetInviteText -> Bool
$c== :: GetInviteText -> GetInviteText -> Bool
Eq, (forall x. GetInviteText -> Rep GetInviteText x)
-> (forall x. Rep GetInviteText x -> GetInviteText)
-> Generic GetInviteText
forall x. Rep GetInviteText x -> GetInviteText
forall x. GetInviteText -> Rep GetInviteText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetInviteText x -> GetInviteText
$cfrom :: forall x. GetInviteText -> Rep GetInviteText x
Generic)

-- | Parameter of Function getDeepLinkInfo
data GetDeepLinkInfo
  = -- | Returns information about a tg:// deep link. Use "tg://need_update_for_some_feature" or "tg:some_unsupported_feature" for testing. Returns a 404 error for unknown links. Can be called before authorization
    GetDeepLinkInfo
      { -- | The link
        GetDeepLinkInfo -> T
link :: T
      }
  deriving (Int -> GetDeepLinkInfo -> ShowS
[GetDeepLinkInfo] -> ShowS
GetDeepLinkInfo -> String
(Int -> GetDeepLinkInfo -> ShowS)
-> (GetDeepLinkInfo -> String)
-> ([GetDeepLinkInfo] -> ShowS)
-> Show GetDeepLinkInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetDeepLinkInfo] -> ShowS
$cshowList :: [GetDeepLinkInfo] -> ShowS
show :: GetDeepLinkInfo -> String
$cshow :: GetDeepLinkInfo -> String
showsPrec :: Int -> GetDeepLinkInfo -> ShowS
$cshowsPrec :: Int -> GetDeepLinkInfo -> ShowS
Show, GetDeepLinkInfo -> GetDeepLinkInfo -> Bool
(GetDeepLinkInfo -> GetDeepLinkInfo -> Bool)
-> (GetDeepLinkInfo -> GetDeepLinkInfo -> Bool)
-> Eq GetDeepLinkInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetDeepLinkInfo -> GetDeepLinkInfo -> Bool
$c/= :: GetDeepLinkInfo -> GetDeepLinkInfo -> Bool
== :: GetDeepLinkInfo -> GetDeepLinkInfo -> Bool
$c== :: GetDeepLinkInfo -> GetDeepLinkInfo -> Bool
Eq, (forall x. GetDeepLinkInfo -> Rep GetDeepLinkInfo x)
-> (forall x. Rep GetDeepLinkInfo x -> GetDeepLinkInfo)
-> Generic GetDeepLinkInfo
forall x. Rep GetDeepLinkInfo x -> GetDeepLinkInfo
forall x. GetDeepLinkInfo -> Rep GetDeepLinkInfo x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetDeepLinkInfo x -> GetDeepLinkInfo
$cfrom :: forall x. GetDeepLinkInfo -> Rep GetDeepLinkInfo x
Generic)

-- | Parameter of Function getApplicationConfig
data GetApplicationConfig
  = -- | Returns application config, provided by the server. Can be called before authorization
    GetApplicationConfig
      {
      }
  deriving (Int -> GetApplicationConfig -> ShowS
[GetApplicationConfig] -> ShowS
GetApplicationConfig -> String
(Int -> GetApplicationConfig -> ShowS)
-> (GetApplicationConfig -> String)
-> ([GetApplicationConfig] -> ShowS)
-> Show GetApplicationConfig
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetApplicationConfig] -> ShowS
$cshowList :: [GetApplicationConfig] -> ShowS
show :: GetApplicationConfig -> String
$cshow :: GetApplicationConfig -> String
showsPrec :: Int -> GetApplicationConfig -> ShowS
$cshowsPrec :: Int -> GetApplicationConfig -> ShowS
Show, GetApplicationConfig -> GetApplicationConfig -> Bool
(GetApplicationConfig -> GetApplicationConfig -> Bool)
-> (GetApplicationConfig -> GetApplicationConfig -> Bool)
-> Eq GetApplicationConfig
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetApplicationConfig -> GetApplicationConfig -> Bool
$c/= :: GetApplicationConfig -> GetApplicationConfig -> Bool
== :: GetApplicationConfig -> GetApplicationConfig -> Bool
$c== :: GetApplicationConfig -> GetApplicationConfig -> Bool
Eq, (forall x. GetApplicationConfig -> Rep GetApplicationConfig x)
-> (forall x. Rep GetApplicationConfig x -> GetApplicationConfig)
-> Generic GetApplicationConfig
forall x. Rep GetApplicationConfig x -> GetApplicationConfig
forall x. GetApplicationConfig -> Rep GetApplicationConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetApplicationConfig x -> GetApplicationConfig
$cfrom :: forall x. GetApplicationConfig -> Rep GetApplicationConfig x
Generic)

-- | Parameter of Function saveApplicationLogEvent
data SaveApplicationLogEvent
  = -- | Saves application log event on the server. Can be called before authorization
    SaveApplicationLogEvent
      { -- | Event type
        SaveApplicationLogEvent -> T
type_ :: T,
        -- | Optional chat identifier, associated with the event
        SaveApplicationLogEvent -> Int
chat_id :: I53,
        -- | The log event data
        SaveApplicationLogEvent -> JsonValue
data_ :: JsonValue
      }
  deriving (Int -> SaveApplicationLogEvent -> ShowS
[SaveApplicationLogEvent] -> ShowS
SaveApplicationLogEvent -> String
(Int -> SaveApplicationLogEvent -> ShowS)
-> (SaveApplicationLogEvent -> String)
-> ([SaveApplicationLogEvent] -> ShowS)
-> Show SaveApplicationLogEvent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SaveApplicationLogEvent] -> ShowS
$cshowList :: [SaveApplicationLogEvent] -> ShowS
show :: SaveApplicationLogEvent -> String
$cshow :: SaveApplicationLogEvent -> String
showsPrec :: Int -> SaveApplicationLogEvent -> ShowS
$cshowsPrec :: Int -> SaveApplicationLogEvent -> ShowS
Show, SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool
(SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool)
-> (SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool)
-> Eq SaveApplicationLogEvent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool
$c/= :: SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool
== :: SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool
$c== :: SaveApplicationLogEvent -> SaveApplicationLogEvent -> Bool
Eq, (forall x.
 SaveApplicationLogEvent -> Rep SaveApplicationLogEvent x)
-> (forall x.
    Rep SaveApplicationLogEvent x -> SaveApplicationLogEvent)
-> Generic SaveApplicationLogEvent
forall x. Rep SaveApplicationLogEvent x -> SaveApplicationLogEvent
forall x. SaveApplicationLogEvent -> Rep SaveApplicationLogEvent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SaveApplicationLogEvent x -> SaveApplicationLogEvent
$cfrom :: forall x. SaveApplicationLogEvent -> Rep SaveApplicationLogEvent x
Generic)

-- | Parameter of Function addProxy
data AddProxy
  = -- | Adds a proxy server for network requests. Can be called before authorization
    AddProxy
      { -- | Proxy server IP address
        AddProxy -> T
server :: T,
        -- | Proxy server port
        AddProxy -> Int
port :: I32,
        -- | True, if the proxy should be enabled
        AddProxy -> Bool
enable :: Bool,
        -- | Proxy type
        AddProxy -> ProxyType
type_ :: ProxyType
      }
  deriving (Int -> AddProxy -> ShowS
[AddProxy] -> ShowS
AddProxy -> String
(Int -> AddProxy -> ShowS)
-> (AddProxy -> String) -> ([AddProxy] -> ShowS) -> Show AddProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddProxy] -> ShowS
$cshowList :: [AddProxy] -> ShowS
show :: AddProxy -> String
$cshow :: AddProxy -> String
showsPrec :: Int -> AddProxy -> ShowS
$cshowsPrec :: Int -> AddProxy -> ShowS
Show, AddProxy -> AddProxy -> Bool
(AddProxy -> AddProxy -> Bool)
-> (AddProxy -> AddProxy -> Bool) -> Eq AddProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddProxy -> AddProxy -> Bool
$c/= :: AddProxy -> AddProxy -> Bool
== :: AddProxy -> AddProxy -> Bool
$c== :: AddProxy -> AddProxy -> Bool
Eq, (forall x. AddProxy -> Rep AddProxy x)
-> (forall x. Rep AddProxy x -> AddProxy) -> Generic AddProxy
forall x. Rep AddProxy x -> AddProxy
forall x. AddProxy -> Rep AddProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddProxy x -> AddProxy
$cfrom :: forall x. AddProxy -> Rep AddProxy x
Generic)

-- | Parameter of Function editProxy
data EditProxy
  = -- | Edits an existing proxy server for network requests. Can be called before authorization
    EditProxy
      { -- | Proxy identifier
        EditProxy -> Int
proxy_id :: I32,
        -- | Proxy server IP address
        EditProxy -> T
server :: T,
        -- | Proxy server port
        EditProxy -> Int
port :: I32,
        -- | True, if the proxy should be enabled
        EditProxy -> Bool
enable :: Bool,
        -- | Proxy type
        EditProxy -> ProxyType
type_ :: ProxyType
      }
  deriving (Int -> EditProxy -> ShowS
[EditProxy] -> ShowS
EditProxy -> String
(Int -> EditProxy -> ShowS)
-> (EditProxy -> String)
-> ([EditProxy] -> ShowS)
-> Show EditProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EditProxy] -> ShowS
$cshowList :: [EditProxy] -> ShowS
show :: EditProxy -> String
$cshow :: EditProxy -> String
showsPrec :: Int -> EditProxy -> ShowS
$cshowsPrec :: Int -> EditProxy -> ShowS
Show, EditProxy -> EditProxy -> Bool
(EditProxy -> EditProxy -> Bool)
-> (EditProxy -> EditProxy -> Bool) -> Eq EditProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EditProxy -> EditProxy -> Bool
$c/= :: EditProxy -> EditProxy -> Bool
== :: EditProxy -> EditProxy -> Bool
$c== :: EditProxy -> EditProxy -> Bool
Eq, (forall x. EditProxy -> Rep EditProxy x)
-> (forall x. Rep EditProxy x -> EditProxy) -> Generic EditProxy
forall x. Rep EditProxy x -> EditProxy
forall x. EditProxy -> Rep EditProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EditProxy x -> EditProxy
$cfrom :: forall x. EditProxy -> Rep EditProxy x
Generic)

-- | Parameter of Function enableProxy
data EnableProxy
  = -- | Enables a proxy. Only one proxy can be enabled at a time. Can be called before authorization
    EnableProxy
      { -- | Proxy identifier
        EnableProxy -> Int
proxy_id :: I32
      }
  deriving (Int -> EnableProxy -> ShowS
[EnableProxy] -> ShowS
EnableProxy -> String
(Int -> EnableProxy -> ShowS)
-> (EnableProxy -> String)
-> ([EnableProxy] -> ShowS)
-> Show EnableProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnableProxy] -> ShowS
$cshowList :: [EnableProxy] -> ShowS
show :: EnableProxy -> String
$cshow :: EnableProxy -> String
showsPrec :: Int -> EnableProxy -> ShowS
$cshowsPrec :: Int -> EnableProxy -> ShowS
Show, EnableProxy -> EnableProxy -> Bool
(EnableProxy -> EnableProxy -> Bool)
-> (EnableProxy -> EnableProxy -> Bool) -> Eq EnableProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnableProxy -> EnableProxy -> Bool
$c/= :: EnableProxy -> EnableProxy -> Bool
== :: EnableProxy -> EnableProxy -> Bool
$c== :: EnableProxy -> EnableProxy -> Bool
Eq, (forall x. EnableProxy -> Rep EnableProxy x)
-> (forall x. Rep EnableProxy x -> EnableProxy)
-> Generic EnableProxy
forall x. Rep EnableProxy x -> EnableProxy
forall x. EnableProxy -> Rep EnableProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep EnableProxy x -> EnableProxy
$cfrom :: forall x. EnableProxy -> Rep EnableProxy x
Generic)

-- | Parameter of Function disableProxy
data DisableProxy
  = -- | Disables the currently enabled proxy. Can be called before authorization
    DisableProxy
      {
      }
  deriving (Int -> DisableProxy -> ShowS
[DisableProxy] -> ShowS
DisableProxy -> String
(Int -> DisableProxy -> ShowS)
-> (DisableProxy -> String)
-> ([DisableProxy] -> ShowS)
-> Show DisableProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisableProxy] -> ShowS
$cshowList :: [DisableProxy] -> ShowS
show :: DisableProxy -> String
$cshow :: DisableProxy -> String
showsPrec :: Int -> DisableProxy -> ShowS
$cshowsPrec :: Int -> DisableProxy -> ShowS
Show, DisableProxy -> DisableProxy -> Bool
(DisableProxy -> DisableProxy -> Bool)
-> (DisableProxy -> DisableProxy -> Bool) -> Eq DisableProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DisableProxy -> DisableProxy -> Bool
$c/= :: DisableProxy -> DisableProxy -> Bool
== :: DisableProxy -> DisableProxy -> Bool
$c== :: DisableProxy -> DisableProxy -> Bool
Eq, (forall x. DisableProxy -> Rep DisableProxy x)
-> (forall x. Rep DisableProxy x -> DisableProxy)
-> Generic DisableProxy
forall x. Rep DisableProxy x -> DisableProxy
forall x. DisableProxy -> Rep DisableProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DisableProxy x -> DisableProxy
$cfrom :: forall x. DisableProxy -> Rep DisableProxy x
Generic)

-- | Parameter of Function removeProxy
data RemoveProxy
  = -- | Removes a proxy server. Can be called before authorization
    RemoveProxy
      { -- | Proxy identifier
        RemoveProxy -> Int
proxy_id :: I32
      }
  deriving (Int -> RemoveProxy -> ShowS
[RemoveProxy] -> ShowS
RemoveProxy -> String
(Int -> RemoveProxy -> ShowS)
-> (RemoveProxy -> String)
-> ([RemoveProxy] -> ShowS)
-> Show RemoveProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RemoveProxy] -> ShowS
$cshowList :: [RemoveProxy] -> ShowS
show :: RemoveProxy -> String
$cshow :: RemoveProxy -> String
showsPrec :: Int -> RemoveProxy -> ShowS
$cshowsPrec :: Int -> RemoveProxy -> ShowS
Show, RemoveProxy -> RemoveProxy -> Bool
(RemoveProxy -> RemoveProxy -> Bool)
-> (RemoveProxy -> RemoveProxy -> Bool) -> Eq RemoveProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RemoveProxy -> RemoveProxy -> Bool
$c/= :: RemoveProxy -> RemoveProxy -> Bool
== :: RemoveProxy -> RemoveProxy -> Bool
$c== :: RemoveProxy -> RemoveProxy -> Bool
Eq, (forall x. RemoveProxy -> Rep RemoveProxy x)
-> (forall x. Rep RemoveProxy x -> RemoveProxy)
-> Generic RemoveProxy
forall x. Rep RemoveProxy x -> RemoveProxy
forall x. RemoveProxy -> Rep RemoveProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RemoveProxy x -> RemoveProxy
$cfrom :: forall x. RemoveProxy -> Rep RemoveProxy x
Generic)

-- | Parameter of Function getProxies
data GetProxies
  = -- | Returns list of proxies that are currently set up. Can be called before authorization
    GetProxies
      {
      }
  deriving (Int -> GetProxies -> ShowS
[GetProxies] -> ShowS
GetProxies -> String
(Int -> GetProxies -> ShowS)
-> (GetProxies -> String)
-> ([GetProxies] -> ShowS)
-> Show GetProxies
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetProxies] -> ShowS
$cshowList :: [GetProxies] -> ShowS
show :: GetProxies -> String
$cshow :: GetProxies -> String
showsPrec :: Int -> GetProxies -> ShowS
$cshowsPrec :: Int -> GetProxies -> ShowS
Show, GetProxies -> GetProxies -> Bool
(GetProxies -> GetProxies -> Bool)
-> (GetProxies -> GetProxies -> Bool) -> Eq GetProxies
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetProxies -> GetProxies -> Bool
$c/= :: GetProxies -> GetProxies -> Bool
== :: GetProxies -> GetProxies -> Bool
$c== :: GetProxies -> GetProxies -> Bool
Eq, (forall x. GetProxies -> Rep GetProxies x)
-> (forall x. Rep GetProxies x -> GetProxies) -> Generic GetProxies
forall x. Rep GetProxies x -> GetProxies
forall x. GetProxies -> Rep GetProxies x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetProxies x -> GetProxies
$cfrom :: forall x. GetProxies -> Rep GetProxies x
Generic)

-- | Parameter of Function getProxyLink
data GetProxyLink
  = -- | Returns an HTTPS link, which can be used to add a proxy. Available only for SOCKS5 and MTProto proxies. Can be called before authorization
    GetProxyLink
      { -- | Proxy identifier
        GetProxyLink -> Int
proxy_id :: I32
      }
  deriving (Int -> GetProxyLink -> ShowS
[GetProxyLink] -> ShowS
GetProxyLink -> String
(Int -> GetProxyLink -> ShowS)
-> (GetProxyLink -> String)
-> ([GetProxyLink] -> ShowS)
-> Show GetProxyLink
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetProxyLink] -> ShowS
$cshowList :: [GetProxyLink] -> ShowS
show :: GetProxyLink -> String
$cshow :: GetProxyLink -> String
showsPrec :: Int -> GetProxyLink -> ShowS
$cshowsPrec :: Int -> GetProxyLink -> ShowS
Show, GetProxyLink -> GetProxyLink -> Bool
(GetProxyLink -> GetProxyLink -> Bool)
-> (GetProxyLink -> GetProxyLink -> Bool) -> Eq GetProxyLink
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetProxyLink -> GetProxyLink -> Bool
$c/= :: GetProxyLink -> GetProxyLink -> Bool
== :: GetProxyLink -> GetProxyLink -> Bool
$c== :: GetProxyLink -> GetProxyLink -> Bool
Eq, (forall x. GetProxyLink -> Rep GetProxyLink x)
-> (forall x. Rep GetProxyLink x -> GetProxyLink)
-> Generic GetProxyLink
forall x. Rep GetProxyLink x -> GetProxyLink
forall x. GetProxyLink -> Rep GetProxyLink x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetProxyLink x -> GetProxyLink
$cfrom :: forall x. GetProxyLink -> Rep GetProxyLink x
Generic)

-- | Parameter of Function pingProxy
data PingProxy
  = -- | Computes time needed to receive a response from a Telegram server through a proxy. Can be called before authorization
    PingProxy
      { -- | Proxy identifier. Use 0 to ping a Telegram server without a proxy
        PingProxy -> Int
proxy_id :: I32
      }
  deriving (Int -> PingProxy -> ShowS
[PingProxy] -> ShowS
PingProxy -> String
(Int -> PingProxy -> ShowS)
-> (PingProxy -> String)
-> ([PingProxy] -> ShowS)
-> Show PingProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PingProxy] -> ShowS
$cshowList :: [PingProxy] -> ShowS
show :: PingProxy -> String
$cshow :: PingProxy -> String
showsPrec :: Int -> PingProxy -> ShowS
$cshowsPrec :: Int -> PingProxy -> ShowS
Show, PingProxy -> PingProxy -> Bool
(PingProxy -> PingProxy -> Bool)
-> (PingProxy -> PingProxy -> Bool) -> Eq PingProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PingProxy -> PingProxy -> Bool
$c/= :: PingProxy -> PingProxy -> Bool
== :: PingProxy -> PingProxy -> Bool
$c== :: PingProxy -> PingProxy -> Bool
Eq, (forall x. PingProxy -> Rep PingProxy x)
-> (forall x. Rep PingProxy x -> PingProxy) -> Generic PingProxy
forall x. Rep PingProxy x -> PingProxy
forall x. PingProxy -> Rep PingProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PingProxy x -> PingProxy
$cfrom :: forall x. PingProxy -> Rep PingProxy x
Generic)

-- | Parameter of Function setLogStream
data SetLogStream
  = -- | Sets new log stream for internal logging of TDLib. This is an offline method. Can be called before authorization. Can be called synchronously
    SetLogStream
      { -- | New log stream
        SetLogStream -> LogStream
log_stream :: LogStream
      }
  deriving (Int -> SetLogStream -> ShowS
[SetLogStream] -> ShowS
SetLogStream -> String
(Int -> SetLogStream -> ShowS)
-> (SetLogStream -> String)
-> ([SetLogStream] -> ShowS)
-> Show SetLogStream
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetLogStream] -> ShowS
$cshowList :: [SetLogStream] -> ShowS
show :: SetLogStream -> String
$cshow :: SetLogStream -> String
showsPrec :: Int -> SetLogStream -> ShowS
$cshowsPrec :: Int -> SetLogStream -> ShowS
Show, SetLogStream -> SetLogStream -> Bool
(SetLogStream -> SetLogStream -> Bool)
-> (SetLogStream -> SetLogStream -> Bool) -> Eq SetLogStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLogStream -> SetLogStream -> Bool
$c/= :: SetLogStream -> SetLogStream -> Bool
== :: SetLogStream -> SetLogStream -> Bool
$c== :: SetLogStream -> SetLogStream -> Bool
Eq, (forall x. SetLogStream -> Rep SetLogStream x)
-> (forall x. Rep SetLogStream x -> SetLogStream)
-> Generic SetLogStream
forall x. Rep SetLogStream x -> SetLogStream
forall x. SetLogStream -> Rep SetLogStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetLogStream x -> SetLogStream
$cfrom :: forall x. SetLogStream -> Rep SetLogStream x
Generic)

-- | Parameter of Function getLogStream
data GetLogStream
  = -- | Returns information about currently used log stream for internal logging of TDLib. This is an offline method. Can be called before authorization. Can be called synchronously
    GetLogStream
      {
      }
  deriving (Int -> GetLogStream -> ShowS
[GetLogStream] -> ShowS
GetLogStream -> String
(Int -> GetLogStream -> ShowS)
-> (GetLogStream -> String)
-> ([GetLogStream] -> ShowS)
-> Show GetLogStream
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogStream] -> ShowS
$cshowList :: [GetLogStream] -> ShowS
show :: GetLogStream -> String
$cshow :: GetLogStream -> String
showsPrec :: Int -> GetLogStream -> ShowS
$cshowsPrec :: Int -> GetLogStream -> ShowS
Show, GetLogStream -> GetLogStream -> Bool
(GetLogStream -> GetLogStream -> Bool)
-> (GetLogStream -> GetLogStream -> Bool) -> Eq GetLogStream
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogStream -> GetLogStream -> Bool
$c/= :: GetLogStream -> GetLogStream -> Bool
== :: GetLogStream -> GetLogStream -> Bool
$c== :: GetLogStream -> GetLogStream -> Bool
Eq, (forall x. GetLogStream -> Rep GetLogStream x)
-> (forall x. Rep GetLogStream x -> GetLogStream)
-> Generic GetLogStream
forall x. Rep GetLogStream x -> GetLogStream
forall x. GetLogStream -> Rep GetLogStream x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLogStream x -> GetLogStream
$cfrom :: forall x. GetLogStream -> Rep GetLogStream x
Generic)

-- | Parameter of Function setLogVerbosityLevel
data SetLogVerbosityLevel
  = -- | Sets the verbosity level of the internal logging of TDLib. This is an offline method. Can be called before authorization. Can be called synchronously
    SetLogVerbosityLevel
      { -- | New value of the verbosity level for logging. Value 0 corresponds to fatal errors, value 1 corresponds to errors, value 2 corresponds to warnings and debug warnings, value 3 corresponds to informational, value 4 corresponds to debug, value 5 corresponds to verbose debug, value greater than 5 and up to 1023 can be used to enable even more logging
        SetLogVerbosityLevel -> Int
new_verbosity_level :: I32
      }
  deriving (Int -> SetLogVerbosityLevel -> ShowS
[SetLogVerbosityLevel] -> ShowS
SetLogVerbosityLevel -> String
(Int -> SetLogVerbosityLevel -> ShowS)
-> (SetLogVerbosityLevel -> String)
-> ([SetLogVerbosityLevel] -> ShowS)
-> Show SetLogVerbosityLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetLogVerbosityLevel] -> ShowS
$cshowList :: [SetLogVerbosityLevel] -> ShowS
show :: SetLogVerbosityLevel -> String
$cshow :: SetLogVerbosityLevel -> String
showsPrec :: Int -> SetLogVerbosityLevel -> ShowS
$cshowsPrec :: Int -> SetLogVerbosityLevel -> ShowS
Show, SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool
(SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool)
-> (SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool)
-> Eq SetLogVerbosityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool
$c/= :: SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool
== :: SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool
$c== :: SetLogVerbosityLevel -> SetLogVerbosityLevel -> Bool
Eq, (forall x. SetLogVerbosityLevel -> Rep SetLogVerbosityLevel x)
-> (forall x. Rep SetLogVerbosityLevel x -> SetLogVerbosityLevel)
-> Generic SetLogVerbosityLevel
forall x. Rep SetLogVerbosityLevel x -> SetLogVerbosityLevel
forall x. SetLogVerbosityLevel -> Rep SetLogVerbosityLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetLogVerbosityLevel x -> SetLogVerbosityLevel
$cfrom :: forall x. SetLogVerbosityLevel -> Rep SetLogVerbosityLevel x
Generic)

-- | Parameter of Function getLogVerbosityLevel
data GetLogVerbosityLevel
  = -- | Returns current verbosity level of the internal logging of TDLib. This is an offline method. Can be called before authorization. Can be called synchronously
    GetLogVerbosityLevel
      {
      }
  deriving (Int -> GetLogVerbosityLevel -> ShowS
[GetLogVerbosityLevel] -> ShowS
GetLogVerbosityLevel -> String
(Int -> GetLogVerbosityLevel -> ShowS)
-> (GetLogVerbosityLevel -> String)
-> ([GetLogVerbosityLevel] -> ShowS)
-> Show GetLogVerbosityLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogVerbosityLevel] -> ShowS
$cshowList :: [GetLogVerbosityLevel] -> ShowS
show :: GetLogVerbosityLevel -> String
$cshow :: GetLogVerbosityLevel -> String
showsPrec :: Int -> GetLogVerbosityLevel -> ShowS
$cshowsPrec :: Int -> GetLogVerbosityLevel -> ShowS
Show, GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool
(GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool)
-> (GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool)
-> Eq GetLogVerbosityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool
$c/= :: GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool
== :: GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool
$c== :: GetLogVerbosityLevel -> GetLogVerbosityLevel -> Bool
Eq, (forall x. GetLogVerbosityLevel -> Rep GetLogVerbosityLevel x)
-> (forall x. Rep GetLogVerbosityLevel x -> GetLogVerbosityLevel)
-> Generic GetLogVerbosityLevel
forall x. Rep GetLogVerbosityLevel x -> GetLogVerbosityLevel
forall x. GetLogVerbosityLevel -> Rep GetLogVerbosityLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLogVerbosityLevel x -> GetLogVerbosityLevel
$cfrom :: forall x. GetLogVerbosityLevel -> Rep GetLogVerbosityLevel x
Generic)

-- | Parameter of Function getLogTags
data GetLogTags
  = -- | Returns list of available TDLib internal log tags, for example, ["actor", "binlog", "connections", "notifications", "proxy"]. This is an offline method. Can be called before authorization. Can be called synchronously
    GetLogTags
      {
      }
  deriving (Int -> GetLogTags -> ShowS
[GetLogTags] -> ShowS
GetLogTags -> String
(Int -> GetLogTags -> ShowS)
-> (GetLogTags -> String)
-> ([GetLogTags] -> ShowS)
-> Show GetLogTags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogTags] -> ShowS
$cshowList :: [GetLogTags] -> ShowS
show :: GetLogTags -> String
$cshow :: GetLogTags -> String
showsPrec :: Int -> GetLogTags -> ShowS
$cshowsPrec :: Int -> GetLogTags -> ShowS
Show, GetLogTags -> GetLogTags -> Bool
(GetLogTags -> GetLogTags -> Bool)
-> (GetLogTags -> GetLogTags -> Bool) -> Eq GetLogTags
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogTags -> GetLogTags -> Bool
$c/= :: GetLogTags -> GetLogTags -> Bool
== :: GetLogTags -> GetLogTags -> Bool
$c== :: GetLogTags -> GetLogTags -> Bool
Eq, (forall x. GetLogTags -> Rep GetLogTags x)
-> (forall x. Rep GetLogTags x -> GetLogTags) -> Generic GetLogTags
forall x. Rep GetLogTags x -> GetLogTags
forall x. GetLogTags -> Rep GetLogTags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLogTags x -> GetLogTags
$cfrom :: forall x. GetLogTags -> Rep GetLogTags x
Generic)

-- | Parameter of Function setLogTagVerbosityLevel
data SetLogTagVerbosityLevel
  = -- | Sets the verbosity level for a specified TDLib internal log tag. This is an offline method. Can be called before authorization. Can be called synchronously
    SetLogTagVerbosityLevel
      { -- | Logging tag to change verbosity level
        SetLogTagVerbosityLevel -> T
tag :: T,
        -- | New verbosity level; 1-1024
        SetLogTagVerbosityLevel -> Int
new_verbosity_level :: I32
      }
  deriving (Int -> SetLogTagVerbosityLevel -> ShowS
[SetLogTagVerbosityLevel] -> ShowS
SetLogTagVerbosityLevel -> String
(Int -> SetLogTagVerbosityLevel -> ShowS)
-> (SetLogTagVerbosityLevel -> String)
-> ([SetLogTagVerbosityLevel] -> ShowS)
-> Show SetLogTagVerbosityLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetLogTagVerbosityLevel] -> ShowS
$cshowList :: [SetLogTagVerbosityLevel] -> ShowS
show :: SetLogTagVerbosityLevel -> String
$cshow :: SetLogTagVerbosityLevel -> String
showsPrec :: Int -> SetLogTagVerbosityLevel -> ShowS
$cshowsPrec :: Int -> SetLogTagVerbosityLevel -> ShowS
Show, SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool
(SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool)
-> (SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool)
-> Eq SetLogTagVerbosityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool
$c/= :: SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool
== :: SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool
$c== :: SetLogTagVerbosityLevel -> SetLogTagVerbosityLevel -> Bool
Eq, (forall x.
 SetLogTagVerbosityLevel -> Rep SetLogTagVerbosityLevel x)
-> (forall x.
    Rep SetLogTagVerbosityLevel x -> SetLogTagVerbosityLevel)
-> Generic SetLogTagVerbosityLevel
forall x. Rep SetLogTagVerbosityLevel x -> SetLogTagVerbosityLevel
forall x. SetLogTagVerbosityLevel -> Rep SetLogTagVerbosityLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetLogTagVerbosityLevel x -> SetLogTagVerbosityLevel
$cfrom :: forall x. SetLogTagVerbosityLevel -> Rep SetLogTagVerbosityLevel x
Generic)

-- | Parameter of Function getLogTagVerbosityLevel
data GetLogTagVerbosityLevel
  = -- | Returns current verbosity level for a specified TDLib internal log tag. This is an offline method. Can be called before authorization. Can be called synchronously
    GetLogTagVerbosityLevel
      { -- | Logging tag to change verbosity level
        GetLogTagVerbosityLevel -> T
tag :: T
      }
  deriving (Int -> GetLogTagVerbosityLevel -> ShowS
[GetLogTagVerbosityLevel] -> ShowS
GetLogTagVerbosityLevel -> String
(Int -> GetLogTagVerbosityLevel -> ShowS)
-> (GetLogTagVerbosityLevel -> String)
-> ([GetLogTagVerbosityLevel] -> ShowS)
-> Show GetLogTagVerbosityLevel
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetLogTagVerbosityLevel] -> ShowS
$cshowList :: [GetLogTagVerbosityLevel] -> ShowS
show :: GetLogTagVerbosityLevel -> String
$cshow :: GetLogTagVerbosityLevel -> String
showsPrec :: Int -> GetLogTagVerbosityLevel -> ShowS
$cshowsPrec :: Int -> GetLogTagVerbosityLevel -> ShowS
Show, GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool
(GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool)
-> (GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool)
-> Eq GetLogTagVerbosityLevel
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool
$c/= :: GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool
== :: GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool
$c== :: GetLogTagVerbosityLevel -> GetLogTagVerbosityLevel -> Bool
Eq, (forall x.
 GetLogTagVerbosityLevel -> Rep GetLogTagVerbosityLevel x)
-> (forall x.
    Rep GetLogTagVerbosityLevel x -> GetLogTagVerbosityLevel)
-> Generic GetLogTagVerbosityLevel
forall x. Rep GetLogTagVerbosityLevel x -> GetLogTagVerbosityLevel
forall x. GetLogTagVerbosityLevel -> Rep GetLogTagVerbosityLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetLogTagVerbosityLevel x -> GetLogTagVerbosityLevel
$cfrom :: forall x. GetLogTagVerbosityLevel -> Rep GetLogTagVerbosityLevel x
Generic)

-- | Parameter of Function addLogMessage
data AddLogMessage
  = -- | Adds a message to TDLib internal log. This is an offline method. Can be called before authorization. Can be called synchronously
    AddLogMessage
      { -- | The minimum verbosity level needed for the message to be logged, 0-1023
        AddLogMessage -> Int
verbosity_level :: I32,
        -- | Text of a message to log
        AddLogMessage -> T
text :: T
      }
  deriving (Int -> AddLogMessage -> ShowS
[AddLogMessage] -> ShowS
AddLogMessage -> String
(Int -> AddLogMessage -> ShowS)
-> (AddLogMessage -> String)
-> ([AddLogMessage] -> ShowS)
-> Show AddLogMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddLogMessage] -> ShowS
$cshowList :: [AddLogMessage] -> ShowS
show :: AddLogMessage -> String
$cshow :: AddLogMessage -> String
showsPrec :: Int -> AddLogMessage -> ShowS
$cshowsPrec :: Int -> AddLogMessage -> ShowS
Show, AddLogMessage -> AddLogMessage -> Bool
(AddLogMessage -> AddLogMessage -> Bool)
-> (AddLogMessage -> AddLogMessage -> Bool) -> Eq AddLogMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddLogMessage -> AddLogMessage -> Bool
$c/= :: AddLogMessage -> AddLogMessage -> Bool
== :: AddLogMessage -> AddLogMessage -> Bool
$c== :: AddLogMessage -> AddLogMessage -> Bool
Eq, (forall x. AddLogMessage -> Rep AddLogMessage x)
-> (forall x. Rep AddLogMessage x -> AddLogMessage)
-> Generic AddLogMessage
forall x. Rep AddLogMessage x -> AddLogMessage
forall x. AddLogMessage -> Rep AddLogMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddLogMessage x -> AddLogMessage
$cfrom :: forall x. AddLogMessage -> Rep AddLogMessage x
Generic)

-- | Parameter of Function testCallEmpty
data TestCallEmpty
  = -- | Does nothing; for testing only. This is an offline method. Can be called before authorization
    TestCallEmpty
      {
      }
  deriving (Int -> TestCallEmpty -> ShowS
[TestCallEmpty] -> ShowS
TestCallEmpty -> String
(Int -> TestCallEmpty -> ShowS)
-> (TestCallEmpty -> String)
-> ([TestCallEmpty] -> ShowS)
-> Show TestCallEmpty
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallEmpty] -> ShowS
$cshowList :: [TestCallEmpty] -> ShowS
show :: TestCallEmpty -> String
$cshow :: TestCallEmpty -> String
showsPrec :: Int -> TestCallEmpty -> ShowS
$cshowsPrec :: Int -> TestCallEmpty -> ShowS
Show, TestCallEmpty -> TestCallEmpty -> Bool
(TestCallEmpty -> TestCallEmpty -> Bool)
-> (TestCallEmpty -> TestCallEmpty -> Bool) -> Eq TestCallEmpty
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallEmpty -> TestCallEmpty -> Bool
$c/= :: TestCallEmpty -> TestCallEmpty -> Bool
== :: TestCallEmpty -> TestCallEmpty -> Bool
$c== :: TestCallEmpty -> TestCallEmpty -> Bool
Eq, (forall x. TestCallEmpty -> Rep TestCallEmpty x)
-> (forall x. Rep TestCallEmpty x -> TestCallEmpty)
-> Generic TestCallEmpty
forall x. Rep TestCallEmpty x -> TestCallEmpty
forall x. TestCallEmpty -> Rep TestCallEmpty x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallEmpty x -> TestCallEmpty
$cfrom :: forall x. TestCallEmpty -> Rep TestCallEmpty x
Generic)

-- | Parameter of Function testCallString
data TestCallString
  = -- | Returns the received string; for testing only. This is an offline method. Can be called before authorization
    TestCallString
      { -- | String to return
        TestCallString -> T
x :: T
      }
  deriving (Int -> TestCallString -> ShowS
[TestCallString] -> ShowS
TestCallString -> String
(Int -> TestCallString -> ShowS)
-> (TestCallString -> String)
-> ([TestCallString] -> ShowS)
-> Show TestCallString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallString] -> ShowS
$cshowList :: [TestCallString] -> ShowS
show :: TestCallString -> String
$cshow :: TestCallString -> String
showsPrec :: Int -> TestCallString -> ShowS
$cshowsPrec :: Int -> TestCallString -> ShowS
Show, TestCallString -> TestCallString -> Bool
(TestCallString -> TestCallString -> Bool)
-> (TestCallString -> TestCallString -> Bool) -> Eq TestCallString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallString -> TestCallString -> Bool
$c/= :: TestCallString -> TestCallString -> Bool
== :: TestCallString -> TestCallString -> Bool
$c== :: TestCallString -> TestCallString -> Bool
Eq, (forall x. TestCallString -> Rep TestCallString x)
-> (forall x. Rep TestCallString x -> TestCallString)
-> Generic TestCallString
forall x. Rep TestCallString x -> TestCallString
forall x. TestCallString -> Rep TestCallString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallString x -> TestCallString
$cfrom :: forall x. TestCallString -> Rep TestCallString x
Generic)

-- | Parameter of Function testCallBytes
data TestCallBytes
  = -- | Returns the received bytes; for testing only. This is an offline method. Can be called before authorization
    TestCallBytes
      { -- | Bytes to return
        TestCallBytes -> ByteString64
x :: ByteString64
      }
  deriving (Int -> TestCallBytes -> ShowS
[TestCallBytes] -> ShowS
TestCallBytes -> String
(Int -> TestCallBytes -> ShowS)
-> (TestCallBytes -> String)
-> ([TestCallBytes] -> ShowS)
-> Show TestCallBytes
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallBytes] -> ShowS
$cshowList :: [TestCallBytes] -> ShowS
show :: TestCallBytes -> String
$cshow :: TestCallBytes -> String
showsPrec :: Int -> TestCallBytes -> ShowS
$cshowsPrec :: Int -> TestCallBytes -> ShowS
Show, TestCallBytes -> TestCallBytes -> Bool
(TestCallBytes -> TestCallBytes -> Bool)
-> (TestCallBytes -> TestCallBytes -> Bool) -> Eq TestCallBytes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallBytes -> TestCallBytes -> Bool
$c/= :: TestCallBytes -> TestCallBytes -> Bool
== :: TestCallBytes -> TestCallBytes -> Bool
$c== :: TestCallBytes -> TestCallBytes -> Bool
Eq, (forall x. TestCallBytes -> Rep TestCallBytes x)
-> (forall x. Rep TestCallBytes x -> TestCallBytes)
-> Generic TestCallBytes
forall x. Rep TestCallBytes x -> TestCallBytes
forall x. TestCallBytes -> Rep TestCallBytes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallBytes x -> TestCallBytes
$cfrom :: forall x. TestCallBytes -> Rep TestCallBytes x
Generic)

-- | Parameter of Function testCallVectorInt
data TestCallVectorInt
  = -- | Returns the received vector of numbers; for testing only. This is an offline method. Can be called before authorization
    TestCallVectorInt
      { -- | Vector of numbers to return
        TestCallVectorInt -> [Int]
x :: ([]) (I32)
      }
  deriving (Int -> TestCallVectorInt -> ShowS
[TestCallVectorInt] -> ShowS
TestCallVectorInt -> String
(Int -> TestCallVectorInt -> ShowS)
-> (TestCallVectorInt -> String)
-> ([TestCallVectorInt] -> ShowS)
-> Show TestCallVectorInt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallVectorInt] -> ShowS
$cshowList :: [TestCallVectorInt] -> ShowS
show :: TestCallVectorInt -> String
$cshow :: TestCallVectorInt -> String
showsPrec :: Int -> TestCallVectorInt -> ShowS
$cshowsPrec :: Int -> TestCallVectorInt -> ShowS
Show, TestCallVectorInt -> TestCallVectorInt -> Bool
(TestCallVectorInt -> TestCallVectorInt -> Bool)
-> (TestCallVectorInt -> TestCallVectorInt -> Bool)
-> Eq TestCallVectorInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallVectorInt -> TestCallVectorInt -> Bool
$c/= :: TestCallVectorInt -> TestCallVectorInt -> Bool
== :: TestCallVectorInt -> TestCallVectorInt -> Bool
$c== :: TestCallVectorInt -> TestCallVectorInt -> Bool
Eq, (forall x. TestCallVectorInt -> Rep TestCallVectorInt x)
-> (forall x. Rep TestCallVectorInt x -> TestCallVectorInt)
-> Generic TestCallVectorInt
forall x. Rep TestCallVectorInt x -> TestCallVectorInt
forall x. TestCallVectorInt -> Rep TestCallVectorInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallVectorInt x -> TestCallVectorInt
$cfrom :: forall x. TestCallVectorInt -> Rep TestCallVectorInt x
Generic)

-- | Parameter of Function testCallVectorIntObject
data TestCallVectorIntObject
  = -- | Returns the received vector of objects containing a number; for testing only. This is an offline method. Can be called before authorization
    TestCallVectorIntObject
      { -- | Vector of objects to return
        TestCallVectorIntObject -> [TestInt]
x :: ([]) (TestInt)
      }
  deriving (Int -> TestCallVectorIntObject -> ShowS
[TestCallVectorIntObject] -> ShowS
TestCallVectorIntObject -> String
(Int -> TestCallVectorIntObject -> ShowS)
-> (TestCallVectorIntObject -> String)
-> ([TestCallVectorIntObject] -> ShowS)
-> Show TestCallVectorIntObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallVectorIntObject] -> ShowS
$cshowList :: [TestCallVectorIntObject] -> ShowS
show :: TestCallVectorIntObject -> String
$cshow :: TestCallVectorIntObject -> String
showsPrec :: Int -> TestCallVectorIntObject -> ShowS
$cshowsPrec :: Int -> TestCallVectorIntObject -> ShowS
Show, TestCallVectorIntObject -> TestCallVectorIntObject -> Bool
(TestCallVectorIntObject -> TestCallVectorIntObject -> Bool)
-> (TestCallVectorIntObject -> TestCallVectorIntObject -> Bool)
-> Eq TestCallVectorIntObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallVectorIntObject -> TestCallVectorIntObject -> Bool
$c/= :: TestCallVectorIntObject -> TestCallVectorIntObject -> Bool
== :: TestCallVectorIntObject -> TestCallVectorIntObject -> Bool
$c== :: TestCallVectorIntObject -> TestCallVectorIntObject -> Bool
Eq, (forall x.
 TestCallVectorIntObject -> Rep TestCallVectorIntObject x)
-> (forall x.
    Rep TestCallVectorIntObject x -> TestCallVectorIntObject)
-> Generic TestCallVectorIntObject
forall x. Rep TestCallVectorIntObject x -> TestCallVectorIntObject
forall x. TestCallVectorIntObject -> Rep TestCallVectorIntObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallVectorIntObject x -> TestCallVectorIntObject
$cfrom :: forall x. TestCallVectorIntObject -> Rep TestCallVectorIntObject x
Generic)

-- | Parameter of Function testCallVectorString
data TestCallVectorString
  = -- | Returns the received vector of strings; for testing only. This is an offline method. Can be called before authorization
    TestCallVectorString
      { -- | Vector of strings to return
        TestCallVectorString -> [T]
x :: ([]) (T)
      }
  deriving (Int -> TestCallVectorString -> ShowS
[TestCallVectorString] -> ShowS
TestCallVectorString -> String
(Int -> TestCallVectorString -> ShowS)
-> (TestCallVectorString -> String)
-> ([TestCallVectorString] -> ShowS)
-> Show TestCallVectorString
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallVectorString] -> ShowS
$cshowList :: [TestCallVectorString] -> ShowS
show :: TestCallVectorString -> String
$cshow :: TestCallVectorString -> String
showsPrec :: Int -> TestCallVectorString -> ShowS
$cshowsPrec :: Int -> TestCallVectorString -> ShowS
Show, TestCallVectorString -> TestCallVectorString -> Bool
(TestCallVectorString -> TestCallVectorString -> Bool)
-> (TestCallVectorString -> TestCallVectorString -> Bool)
-> Eq TestCallVectorString
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallVectorString -> TestCallVectorString -> Bool
$c/= :: TestCallVectorString -> TestCallVectorString -> Bool
== :: TestCallVectorString -> TestCallVectorString -> Bool
$c== :: TestCallVectorString -> TestCallVectorString -> Bool
Eq, (forall x. TestCallVectorString -> Rep TestCallVectorString x)
-> (forall x. Rep TestCallVectorString x -> TestCallVectorString)
-> Generic TestCallVectorString
forall x. Rep TestCallVectorString x -> TestCallVectorString
forall x. TestCallVectorString -> Rep TestCallVectorString x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestCallVectorString x -> TestCallVectorString
$cfrom :: forall x. TestCallVectorString -> Rep TestCallVectorString x
Generic)

-- | Parameter of Function testCallVectorStringObject
data TestCallVectorStringObject
  = -- | Returns the received vector of objects containing a string; for testing only. This is an offline method. Can be called before authorization
    TestCallVectorStringObject
      { -- | Vector of objects to return
        TestCallVectorStringObject -> [TestString]
x :: ([]) (TestString)
      }
  deriving (Int -> TestCallVectorStringObject -> ShowS
[TestCallVectorStringObject] -> ShowS
TestCallVectorStringObject -> String
(Int -> TestCallVectorStringObject -> ShowS)
-> (TestCallVectorStringObject -> String)
-> ([TestCallVectorStringObject] -> ShowS)
-> Show TestCallVectorStringObject
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestCallVectorStringObject] -> ShowS
$cshowList :: [TestCallVectorStringObject] -> ShowS
show :: TestCallVectorStringObject -> String
$cshow :: TestCallVectorStringObject -> String
showsPrec :: Int -> TestCallVectorStringObject -> ShowS
$cshowsPrec :: Int -> TestCallVectorStringObject -> ShowS
Show, TestCallVectorStringObject -> TestCallVectorStringObject -> Bool
(TestCallVectorStringObject -> TestCallVectorStringObject -> Bool)
-> (TestCallVectorStringObject
    -> TestCallVectorStringObject -> Bool)
-> Eq TestCallVectorStringObject
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestCallVectorStringObject -> TestCallVectorStringObject -> Bool
$c/= :: TestCallVectorStringObject -> TestCallVectorStringObject -> Bool
== :: TestCallVectorStringObject -> TestCallVectorStringObject -> Bool
$c== :: TestCallVectorStringObject -> TestCallVectorStringObject -> Bool
Eq, (forall x.
 TestCallVectorStringObject -> Rep TestCallVectorStringObject x)
-> (forall x.
    Rep TestCallVectorStringObject x -> TestCallVectorStringObject)
-> Generic TestCallVectorStringObject
forall x.
Rep TestCallVectorStringObject x -> TestCallVectorStringObject
forall x.
TestCallVectorStringObject -> Rep TestCallVectorStringObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep TestCallVectorStringObject x -> TestCallVectorStringObject
$cfrom :: forall x.
TestCallVectorStringObject -> Rep TestCallVectorStringObject x
Generic)

-- | Parameter of Function testSquareInt
data TestSquareInt
  = -- | Returns the squared received number; for testing only. This is an offline method. Can be called before authorization
    TestSquareInt
      { -- | Number to square
        TestSquareInt -> Int
x :: I32
      }
  deriving (Int -> TestSquareInt -> ShowS
[TestSquareInt] -> ShowS
TestSquareInt -> String
(Int -> TestSquareInt -> ShowS)
-> (TestSquareInt -> String)
-> ([TestSquareInt] -> ShowS)
-> Show TestSquareInt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestSquareInt] -> ShowS
$cshowList :: [TestSquareInt] -> ShowS
show :: TestSquareInt -> String
$cshow :: TestSquareInt -> String
showsPrec :: Int -> TestSquareInt -> ShowS
$cshowsPrec :: Int -> TestSquareInt -> ShowS
Show, TestSquareInt -> TestSquareInt -> Bool
(TestSquareInt -> TestSquareInt -> Bool)
-> (TestSquareInt -> TestSquareInt -> Bool) -> Eq TestSquareInt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestSquareInt -> TestSquareInt -> Bool
$c/= :: TestSquareInt -> TestSquareInt -> Bool
== :: TestSquareInt -> TestSquareInt -> Bool
$c== :: TestSquareInt -> TestSquareInt -> Bool
Eq, (forall x. TestSquareInt -> Rep TestSquareInt x)
-> (forall x. Rep TestSquareInt x -> TestSquareInt)
-> Generic TestSquareInt
forall x. Rep TestSquareInt x -> TestSquareInt
forall x. TestSquareInt -> Rep TestSquareInt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestSquareInt x -> TestSquareInt
$cfrom :: forall x. TestSquareInt -> Rep TestSquareInt x
Generic)

-- | Parameter of Function testNetwork
data TestNetwork
  = -- | Sends a simple network request to the Telegram servers; for testing only. Can be called before authorization
    TestNetwork
      {
      }
  deriving (Int -> TestNetwork -> ShowS
[TestNetwork] -> ShowS
TestNetwork -> String
(Int -> TestNetwork -> ShowS)
-> (TestNetwork -> String)
-> ([TestNetwork] -> ShowS)
-> Show TestNetwork
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestNetwork] -> ShowS
$cshowList :: [TestNetwork] -> ShowS
show :: TestNetwork -> String
$cshow :: TestNetwork -> String
showsPrec :: Int -> TestNetwork -> ShowS
$cshowsPrec :: Int -> TestNetwork -> ShowS
Show, TestNetwork -> TestNetwork -> Bool
(TestNetwork -> TestNetwork -> Bool)
-> (TestNetwork -> TestNetwork -> Bool) -> Eq TestNetwork
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestNetwork -> TestNetwork -> Bool
$c/= :: TestNetwork -> TestNetwork -> Bool
== :: TestNetwork -> TestNetwork -> Bool
$c== :: TestNetwork -> TestNetwork -> Bool
Eq, (forall x. TestNetwork -> Rep TestNetwork x)
-> (forall x. Rep TestNetwork x -> TestNetwork)
-> Generic TestNetwork
forall x. Rep TestNetwork x -> TestNetwork
forall x. TestNetwork -> Rep TestNetwork x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestNetwork x -> TestNetwork
$cfrom :: forall x. TestNetwork -> Rep TestNetwork x
Generic)

-- | Parameter of Function testProxy
data TestProxy
  = -- | Sends a simple network request to the Telegram servers via proxy; for testing only. Can be called before authorization
    TestProxy
      { -- | Proxy server IP address
        TestProxy -> T
server :: T,
        -- | Proxy server port
        TestProxy -> Int
port :: I32,
        -- | Proxy type
        TestProxy -> ProxyType
type_ :: ProxyType,
        -- | Identifier of a datacenter, with which to test connection
        TestProxy -> Int
dc_id :: I32,
        -- | The maximum overall timeout for the request
        TestProxy -> Double
timeout :: Double
      }
  deriving (Int -> TestProxy -> ShowS
[TestProxy] -> ShowS
TestProxy -> String
(Int -> TestProxy -> ShowS)
-> (TestProxy -> String)
-> ([TestProxy] -> ShowS)
-> Show TestProxy
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestProxy] -> ShowS
$cshowList :: [TestProxy] -> ShowS
show :: TestProxy -> String
$cshow :: TestProxy -> String
showsPrec :: Int -> TestProxy -> ShowS
$cshowsPrec :: Int -> TestProxy -> ShowS
Show, TestProxy -> TestProxy -> Bool
(TestProxy -> TestProxy -> Bool)
-> (TestProxy -> TestProxy -> Bool) -> Eq TestProxy
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestProxy -> TestProxy -> Bool
$c/= :: TestProxy -> TestProxy -> Bool
== :: TestProxy -> TestProxy -> Bool
$c== :: TestProxy -> TestProxy -> Bool
Eq, (forall x. TestProxy -> Rep TestProxy x)
-> (forall x. Rep TestProxy x -> TestProxy) -> Generic TestProxy
forall x. Rep TestProxy x -> TestProxy
forall x. TestProxy -> Rep TestProxy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestProxy x -> TestProxy
$cfrom :: forall x. TestProxy -> Rep TestProxy x
Generic)

-- | Parameter of Function testGetDifference
data TestGetDifference
  = -- | Forces an updates.getDifference call to the Telegram servers; for testing only
    TestGetDifference
      {
      }
  deriving (Int -> TestGetDifference -> ShowS
[TestGetDifference] -> ShowS
TestGetDifference -> String
(Int -> TestGetDifference -> ShowS)
-> (TestGetDifference -> String)
-> ([TestGetDifference] -> ShowS)
-> Show TestGetDifference
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestGetDifference] -> ShowS
$cshowList :: [TestGetDifference] -> ShowS
show :: TestGetDifference -> String
$cshow :: TestGetDifference -> String
showsPrec :: Int -> TestGetDifference -> ShowS
$cshowsPrec :: Int -> TestGetDifference -> ShowS
Show, TestGetDifference -> TestGetDifference -> Bool
(TestGetDifference -> TestGetDifference -> Bool)
-> (TestGetDifference -> TestGetDifference -> Bool)
-> Eq TestGetDifference
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestGetDifference -> TestGetDifference -> Bool
$c/= :: TestGetDifference -> TestGetDifference -> Bool
== :: TestGetDifference -> TestGetDifference -> Bool
$c== :: TestGetDifference -> TestGetDifference -> Bool
Eq, (forall x. TestGetDifference -> Rep TestGetDifference x)
-> (forall x. Rep TestGetDifference x -> TestGetDifference)
-> Generic TestGetDifference
forall x. Rep TestGetDifference x -> TestGetDifference
forall x. TestGetDifference -> Rep TestGetDifference x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestGetDifference x -> TestGetDifference
$cfrom :: forall x. TestGetDifference -> Rep TestGetDifference x
Generic)

-- | Parameter of Function testUseUpdate
data TestUseUpdate
  = -- | Does nothing and ensures that the Update object is used; for testing only. This is an offline method. Can be called before authorization
    TestUseUpdate
      {
      }
  deriving (Int -> TestUseUpdate -> ShowS
[TestUseUpdate] -> ShowS
TestUseUpdate -> String
(Int -> TestUseUpdate -> ShowS)
-> (TestUseUpdate -> String)
-> ([TestUseUpdate] -> ShowS)
-> Show TestUseUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestUseUpdate] -> ShowS
$cshowList :: [TestUseUpdate] -> ShowS
show :: TestUseUpdate -> String
$cshow :: TestUseUpdate -> String
showsPrec :: Int -> TestUseUpdate -> ShowS
$cshowsPrec :: Int -> TestUseUpdate -> ShowS
Show, TestUseUpdate -> TestUseUpdate -> Bool
(TestUseUpdate -> TestUseUpdate -> Bool)
-> (TestUseUpdate -> TestUseUpdate -> Bool) -> Eq TestUseUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestUseUpdate -> TestUseUpdate -> Bool
$c/= :: TestUseUpdate -> TestUseUpdate -> Bool
== :: TestUseUpdate -> TestUseUpdate -> Bool
$c== :: TestUseUpdate -> TestUseUpdate -> Bool
Eq, (forall x. TestUseUpdate -> Rep TestUseUpdate x)
-> (forall x. Rep TestUseUpdate x -> TestUseUpdate)
-> Generic TestUseUpdate
forall x. Rep TestUseUpdate x -> TestUseUpdate
forall x. TestUseUpdate -> Rep TestUseUpdate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestUseUpdate x -> TestUseUpdate
$cfrom :: forall x. TestUseUpdate -> Rep TestUseUpdate x
Generic)

-- | Parameter of Function testReturnError
data TestReturnError
  = -- | Returns the specified error and ensures that the Error object is used; for testing only. This is an offline method. Can be called before authorization. Can be called synchronously
    TestReturnError
      { -- | The error to be returned
        TestReturnError -> Error
error :: Error
      }
  deriving (Int -> TestReturnError -> ShowS
[TestReturnError] -> ShowS
TestReturnError -> String
(Int -> TestReturnError -> ShowS)
-> (TestReturnError -> String)
-> ([TestReturnError] -> ShowS)
-> Show TestReturnError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TestReturnError] -> ShowS
$cshowList :: [TestReturnError] -> ShowS
show :: TestReturnError -> String
$cshow :: TestReturnError -> String
showsPrec :: Int -> TestReturnError -> ShowS
$cshowsPrec :: Int -> TestReturnError -> ShowS
Show, TestReturnError -> TestReturnError -> Bool
(TestReturnError -> TestReturnError -> Bool)
-> (TestReturnError -> TestReturnError -> Bool)
-> Eq TestReturnError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestReturnError -> TestReturnError -> Bool
$c/= :: TestReturnError -> TestReturnError -> Bool
== :: TestReturnError -> TestReturnError -> Bool
$c== :: TestReturnError -> TestReturnError -> Bool
Eq, (forall x. TestReturnError -> Rep TestReturnError x)
-> (forall x. Rep TestReturnError x -> TestReturnError)
-> Generic TestReturnError
forall x. Rep TestReturnError x -> TestReturnError
forall x. TestReturnError -> Rep TestReturnError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestReturnError x -> TestReturnError
$cfrom :: forall x. TestReturnError -> Rep TestReturnError x
Generic)

[TestReturnError] -> Encoding
[TestReturnError] -> Value
[TestUseUpdate] -> Encoding
[TestUseUpdate] -> Value
[TestGetDifference] -> Encoding
[TestGetDifference] -> Value
[TestProxy] -> Encoding
[TestProxy] -> Value
[TestNetwork] -> Encoding
[TestNetwork] -> Value
[TestSquareInt] -> Encoding
[TestSquareInt] -> Value
[TestCallVectorStringObject] -> Encoding
[TestCallVectorStringObject] -> Value
[TestCallVectorString] -> Encoding
[TestCallVectorString] -> Value
[TestCallVectorIntObject] -> Encoding
[TestCallVectorIntObject] -> Value
[TestCallVectorInt] -> Encoding
[TestCallVectorInt] -> Value
[TestCallBytes] -> Encoding
[TestCallBytes] -> Value
[TestCallString] -> Encoding
[TestCallString] -> Value
[TestCallEmpty] -> Encoding
[TestCallEmpty] -> Value
[AddLogMessage] -> Encoding
[AddLogMessage] -> Value
[GetLogTagVerbosityLevel] -> Encoding
[GetLogTagVerbosityLevel] -> Value
[SetLogTagVerbosityLevel] -> Encoding
[SetLogTagVerbosityLevel] -> Value
[GetLogTags] -> Encoding
[GetLogTags] -> Value
[GetLogVerbosityLevel] -> Encoding
[GetLogVerbosityLevel] -> Value
[SetLogVerbosityLevel] -> Encoding
[SetLogVerbosityLevel] -> Value
[GetLogStream] -> Encoding
[GetLogStream] -> Value
[SetLogStream] -> Encoding
[SetLogStream] -> Value
[PingProxy] -> Encoding
[PingProxy] -> Value
[GetProxyLink] -> Encoding
[GetProxyLink] -> Value
[GetProxies] -> Encoding
[GetProxies] -> Value
[RemoveProxy] -> Encoding
[RemoveProxy] -> Value
[DisableProxy] -> Encoding
[DisableProxy] -> Value
[EnableProxy] -> Encoding
[EnableProxy] -> Value
[EditProxy] -> Encoding
[EditProxy] -> Value
[AddProxy] -> Encoding
[AddProxy] -> Value
[SaveApplicationLogEvent] -> Encoding
[SaveApplicationLogEvent] -> Value
[GetApplicationConfig] -> Encoding
[GetApplicationConfig] -> Value
[GetDeepLinkInfo] -> Encoding
[GetDeepLinkInfo] -> Value
[GetInviteText] -> Encoding
[GetInviteText] -> Value
[GetCountryCode] -> Encoding
[GetCountryCode] -> Value
[SetAlarm] -> Encoding
[SetAlarm] -> Value
[AnswerCustomQuery] -> Encoding
[AnswerCustomQuery] -> Value
[SendCustomRequest] -> Encoding
[SendCustomRequest] -> Value
[AcceptTermsOfService] -> Encoding
[AcceptTermsOfService] -> Value
[GetMapThumbnailFile] -> Encoding
[GetMapThumbnailFile] -> Value
[RemoveStickerFromSet] -> Encoding
[RemoveStickerFromSet] -> Value
[SetStickerPositionInSet] -> Encoding
[SetStickerPositionInSet] -> Value
[SetStickerSetThumbnail] -> Encoding
[SetStickerSetThumbnail] -> Value
[AddStickerToSet] -> Encoding
[AddStickerToSet] -> Value
[CreateNewStickerSet] -> Encoding
[CreateNewStickerSet] -> Value
[UploadStickerFile] -> Encoding
[UploadStickerFile] -> Value
[SetBotUpdatesStatus] -> Encoding
[SetBotUpdatesStatus] -> Value
[CheckPhoneNumberConfirmationCode] -> Encoding
[CheckPhoneNumberConfirmationCode] -> Value
[ResendPhoneNumberConfirmationCode] -> Encoding
[ResendPhoneNumberConfirmationCode] -> Value
[SendPhoneNumberConfirmationCode] -> Encoding
[SendPhoneNumberConfirmationCode] -> Value
[SendPassportAuthorizationForm] -> Encoding
[SendPassportAuthorizationForm] -> Value
[GetPassportAuthorizationFormAvailableElements] -> Encoding
[GetPassportAuthorizationFormAvailableElements] -> Value
[GetPassportAuthorizationForm] -> Encoding
[GetPassportAuthorizationForm] -> Value
[CheckEmailAddressVerificationCode] -> Encoding
[CheckEmailAddressVerificationCode] -> Value
[ResendEmailAddressVerificationCode] -> Encoding
[ResendEmailAddressVerificationCode] -> Value
[SendEmailAddressVerificationCode] -> Encoding
[SendEmailAddressVerificationCode] -> Value
[CheckPhoneNumberVerificationCode] -> Encoding
[CheckPhoneNumberVerificationCode] -> Value
[ResendPhoneNumberVerificationCode] -> Encoding
[ResendPhoneNumberVerificationCode] -> Value
[SendPhoneNumberVerificationCode] -> Encoding
[SendPhoneNumberVerificationCode] -> Value
[GetPreferredCountryLanguage] -> Encoding
[GetPreferredCountryLanguage] -> Value
[SetPassportElementErrors] -> Encoding
[SetPassportElementErrors] -> Value
[DeletePassportElement] -> Encoding
[DeletePassportElement] -> Value
[SetPassportElement] -> Encoding
[SetPassportElement] -> Value
[GetAllPassportElements] -> Encoding
[GetAllPassportElements] -> Value
[GetPassportElement] -> Encoding
[GetPassportElement] -> Value
[GetBankCardInfo] -> Encoding
[GetBankCardInfo] -> Value
[SetAutoDownloadSettings] -> Encoding
[SetAutoDownloadSettings] -> Value
[GetAutoDownloadSettingsPresets] -> Encoding
[GetAutoDownloadSettingsPresets] -> Value
[ResetNetworkStatistics] -> Encoding
[ResetNetworkStatistics] -> Value
[AddNetworkStatistics] -> Encoding
[AddNetworkStatistics] -> Value
[GetNetworkStatistics] -> Encoding
[GetNetworkStatistics] -> Value
[SetNetworkType] -> Encoding
[SetNetworkType] -> Value
[OptimizeStorage] -> Encoding
[OptimizeStorage] -> Value
[GetDatabaseStatistics] -> Encoding
[GetDatabaseStatistics] -> Value
[GetStorageStatisticsFast] -> Encoding
[GetStorageStatisticsFast] -> Value
[GetStorageStatistics] -> Encoding
[GetStorageStatistics] -> Value
[GetChatStatisticsGraph] -> Encoding
[GetChatStatisticsGraph] -> Value
[GetChatStatistics] -> Encoding
[GetChatStatistics] -> Value
[GetChatStatisticsUrl] -> Encoding
[GetChatStatisticsUrl] -> Value
[ReportChat] -> Encoding
[ReportChat] -> Value
[RemoveChatActionBar] -> Encoding
[RemoveChatActionBar] -> Value
[DeleteAccount] -> Encoding
[DeleteAccount] -> Value
[GetAccountTtl] -> Encoding
[GetAccountTtl] -> Value
[SetAccountTtl] -> Encoding
[SetAccountTtl] -> Value
[SetOption] -> Encoding
[SetOption] -> Value
[GetOption] -> Encoding
[GetOption] -> Value
[GetUserPrivacySettingRules] -> Encoding
[GetUserPrivacySettingRules] -> Value
[SetUserPrivacySettingRules] -> Encoding
[SetUserPrivacySettingRules] -> Value
[GetRecentlyVisitedTMeUrls] -> Encoding
[GetRecentlyVisitedTMeUrls] -> Value
[GetPushReceiverId] -> Encoding
[GetPushReceiverId] -> Value
[ProcessPushNotification] -> Encoding
[ProcessPushNotification] -> Value
[RegisterDevice] -> Encoding
[RegisterDevice] -> Value
[DeleteLanguagePack] -> Encoding
[DeleteLanguagePack] -> Value
[SetCustomLanguagePackString] -> Encoding
[SetCustomLanguagePackString] -> Value
[EditCustomLanguagePackInfo] -> Encoding
[EditCustomLanguagePackInfo] -> Value
[SetCustomLanguagePack] -> Encoding
[SetCustomLanguagePack] -> Value
[AddCustomServerLanguagePack] -> Encoding
[AddCustomServerLanguagePack] -> Value
[SynchronizeLanguagePack] -> Encoding
[SynchronizeLanguagePack] -> Value
[GetLanguagePackStrings] -> Encoding
[GetLanguagePackStrings] -> Value
[GetLanguagePackInfo] -> Encoding
[GetLanguagePackInfo] -> Value
[GetLocalizationTargetInfo] -> Encoding
[GetLocalizationTargetInfo] -> Value
[ResetBackgrounds] -> Encoding
[ResetBackgrounds] -> Value
[RemoveBackground] -> Encoding
[RemoveBackground] -> Value
[SetBackground] -> Encoding
[SetBackground] -> Value
[SearchBackground] -> Encoding
[SearchBackground] -> Value
[GetBackgroundUrl] -> Encoding
[GetBackgroundUrl] -> Value
[GetBackgrounds] -> Encoding
[GetBackgrounds] -> Value
[GetSupportUser] -> Encoding
[GetSupportUser] -> Value
[DeleteSavedCredentials] -> Encoding
[DeleteSavedCredentials] -> Value
[DeleteSavedOrderInfo] -> Encoding
[DeleteSavedOrderInfo] -> Value
[GetSavedOrderInfo] -> Encoding
[GetSavedOrderInfo] -> Value
[GetPaymentReceipt] -> Encoding
[GetPaymentReceipt] -> Value
[SendPaymentForm] -> Encoding
[SendPaymentForm] -> Value
[ValidateOrderInfo] -> Encoding
[ValidateOrderInfo] -> Value
[GetPaymentForm] -> Encoding
[GetPaymentForm] -> Value
[GetChatEventLog] -> Encoding
[GetChatEventLog] -> Value
[CloseSecretChat] -> Encoding
[CloseSecretChat] -> Value
[DeleteSupergroup] -> Encoding
[DeleteSupergroup] -> Value
[GetSupergroupMembers] -> Encoding
[GetSupergroupMembers] -> Value
[ReportSupergroupSpam] -> Encoding
[ReportSupergroupSpam] -> Value
[ToggleSupergroupIsAllHistoryAvailable] -> Encoding
[ToggleSupergroupIsAllHistoryAvailable] -> Value
[ToggleSupergroupSignMessages] -> Encoding
[ToggleSupergroupSignMessages] -> Value
[SetSupergroupStickerSet] -> Encoding
[SetSupergroupStickerSet] -> Value
[SetSupergroupUsername] -> Encoding
[SetSupergroupUsername] -> Value
[DisconnectAllWebsites] -> Encoding
[DisconnectAllWebsites] -> Value
[DisconnectWebsite] -> Encoding
[DisconnectWebsite] -> Value
[GetConnectedWebsites] -> Encoding
[GetConnectedWebsites] -> Value
[TerminateAllOtherSessions] -> Encoding
[TerminateAllOtherSessions] -> Value
[TerminateSession] -> Encoding
[TerminateSession] -> Value
[GetActiveSessions] -> Encoding
[GetActiveSessions] -> Value
[SetCommands] -> Encoding
[SetCommands] -> Value
[CheckChangePhoneNumberCode] -> Encoding
[CheckChangePhoneNumberCode] -> Value
[ResendChangePhoneNumberCode] -> Encoding
[ResendChangePhoneNumberCode] -> Value
[ChangePhoneNumber] -> Encoding
[ChangePhoneNumber] -> Value
[SetLocation] -> Encoding
[SetLocation] -> Value
[SetUsername] -> Encoding
[SetUsername] -> Value
[SetBio] -> Encoding
[SetBio] -> Value
[SetName] -> Encoding
[SetName] -> Value
[DeleteProfilePhoto] -> Encoding
[DeleteProfilePhoto] -> Value
[SetProfilePhoto] -> Encoding
[SetProfilePhoto] -> Value
[GetWebPageInstantView] -> Encoding
[GetWebPageInstantView] -> Value
[GetWebPagePreview] -> Encoding
[GetWebPagePreview] -> Value
[RemoveRecentHashtag] -> Encoding
[RemoveRecentHashtag] -> Value
[SearchHashtags] -> Encoding
[SearchHashtags] -> Value
[GetRecentInlineBots] -> Encoding
[GetRecentInlineBots] -> Value
[RemoveSavedAnimation] -> Encoding
[RemoveSavedAnimation] -> Value
[AddSavedAnimation] -> Encoding
[AddSavedAnimation] -> Value
[GetSavedAnimations] -> Encoding
[GetSavedAnimations] -> Value
[GetEmojiSuggestionsUrl] -> Encoding
[GetEmojiSuggestionsUrl] -> Value
[SearchEmojis] -> Encoding
[SearchEmojis] -> Value
[GetStickerEmojis] -> Encoding
[GetStickerEmojis] -> Value
[RemoveFavoriteSticker] -> Encoding
[RemoveFavoriteSticker] -> Value
[AddFavoriteSticker] -> Encoding
[AddFavoriteSticker] -> Value
[GetFavoriteStickers] -> Encoding
[GetFavoriteStickers] -> Value
[ClearRecentStickers] -> Encoding
[ClearRecentStickers] -> Value
[RemoveRecentSticker] -> Encoding
[RemoveRecentSticker] -> Value
[AddRecentSticker] -> Encoding
[AddRecentSticker] -> Value
[GetRecentStickers] -> Encoding
[GetRecentStickers] -> Value
[ReorderInstalledStickerSets] -> Encoding
[ReorderInstalledStickerSets] -> Value
[ViewTrendingStickerSets] -> Encoding
[ViewTrendingStickerSets] -> Value
[ChangeStickerSet] -> Encoding
[ChangeStickerSet] -> Value
[SearchStickerSets] -> Encoding
[SearchStickerSets] -> Value
[SearchInstalledStickerSets] -> Encoding
[SearchInstalledStickerSets] -> Value
[SearchStickerSet] -> Encoding
[SearchStickerSet] -> Value
[GetStickerSet] -> Encoding
[GetStickerSet] -> Value
[GetAttachedStickerSets] -> Encoding
[GetAttachedStickerSets] -> Value
[GetTrendingStickerSets] -> Encoding
[GetTrendingStickerSets] -> Value
[GetArchivedStickerSets] -> Encoding
[GetArchivedStickerSets] -> Value
[GetInstalledStickerSets] -> Encoding
[GetInstalledStickerSets] -> Value
[SearchStickers] -> Encoding
[SearchStickers] -> Value
[GetStickers] -> Encoding
[GetStickers] -> Value
[GetUserProfilePhotos] -> Encoding
[GetUserProfilePhotos] -> Value
[SharePhoneNumber] -> Encoding
[SharePhoneNumber] -> Value
[ClearImportedContacts] -> Encoding
[ClearImportedContacts] -> Value
[ChangeImportedContacts] -> Encoding
[ChangeImportedContacts] -> Value
[GetImportedContactCount] -> Encoding
[GetImportedContactCount] -> Value
[RemoveContacts] -> Encoding
[RemoveContacts] -> Value
[SearchContacts] -> Encoding
[SearchContacts] -> Value
[GetContacts] -> Encoding
[GetContacts] -> Value
[ImportContacts] -> Encoding
[ImportContacts] -> Value
[AddContact] -> Encoding
[AddContact] -> Value
[GetBlockedUsers] -> Encoding
[GetBlockedUsers] -> Value
[UnblockUser] -> Encoding
[UnblockUser] -> Value
[BlockUser] -> Encoding
[BlockUser] -> Value
[SendCallDebugInformation] -> Encoding
[SendCallDebugInformation] -> Value
[SendCallRating] -> Encoding
[SendCallRating] -> Value
[DiscardCall] -> Encoding
[DiscardCall] -> Value
[AcceptCall] -> Encoding
[AcceptCall] -> Value
[CreateCall] -> Encoding
[CreateCall] -> Value
[JoinChatByInviteLink] -> Encoding
[JoinChatByInviteLink] -> Value
[CheckChatInviteLink] -> Encoding
[CheckChatInviteLink] -> Value
[GenerateChatInviteLink] -> Encoding
[GenerateChatInviteLink] -> Value
[DeleteFile] -> Encoding
[DeleteFile] -> Value
[ReadFilePart] -> Encoding
[ReadFilePart] -> Value
[FinishFileGeneration] -> Encoding
[FinishFileGeneration] -> Value
[SetFileGenerationProgress] -> Encoding
[SetFileGenerationProgress] -> Value
[WriteGeneratedFilePart] -> Encoding
[WriteGeneratedFilePart] -> Value
[CancelUploadFile] -> Encoding
[CancelUploadFile] -> Value
[UploadFile] -> Encoding
[UploadFile] -> Value
[CancelDownloadFile] -> Encoding
[CancelDownloadFile] -> Value
[GetFileDownloadedPrefixSize] -> Encoding
[GetFileDownloadedPrefixSize] -> Value
[DownloadFile] -> Encoding
[DownloadFile] -> Value
[SetPinnedChats] -> Encoding
[SetPinnedChats] -> Value
[ResetAllNotificationSettings] -> Encoding
[ResetAllNotificationSettings] -> Value
[SetScopeNotificationSettings] -> Encoding
[SetScopeNotificationSettings] -> Value
[GetScopeNotificationSettings] -> Encoding
[GetScopeNotificationSettings] -> Value
[GetChatNotificationSettingsExceptions] -> Encoding
[GetChatNotificationSettingsExceptions] -> Value
[ClearAllDraftMessages] -> Encoding
[ClearAllDraftMessages] -> Value
[GetChatAdministrators] -> Encoding
[GetChatAdministrators] -> Value
[SearchChatMembers] -> Encoding
[SearchChatMembers] -> Value
[GetChatMember] -> Encoding
[GetChatMember] -> Value
[TransferChatOwnership] -> Encoding
[TransferChatOwnership] -> Value
[CanTransferOwnership] -> Encoding
[CanTransferOwnership] -> Value
[SetChatMemberStatus] -> Encoding
[SetChatMemberStatus] -> Value
[AddChatMembers] -> Encoding
[AddChatMembers] -> Value
[AddChatMember] -> Encoding
[AddChatMember] -> Value
[LeaveChat] -> Encoding
[LeaveChat] -> Value
[JoinChat] -> Encoding
[JoinChat] -> Value
[UnpinChatMessage] -> Encoding
[UnpinChatMessage] -> Value
[PinChatMessage] -> Encoding
[PinChatMessage] -> Value
[SetChatSlowModeDelay] -> Encoding
[SetChatSlowModeDelay] -> Value
[SetChatLocation] -> Encoding
[SetChatLocation] -> Value
[SetChatDiscussionGroup] -> Encoding
[SetChatDiscussionGroup] -> Value
[SetChatDescription] -> Encoding
[SetChatDescription] -> Value
[SetChatClientData] -> Encoding
[SetChatClientData] -> Value
[ToggleChatDefaultDisableNotification] -> Encoding
[ToggleChatDefaultDisableNotification] -> Value
[ToggleChatIsMarkedAsUnread] -> Encoding
[ToggleChatIsMarkedAsUnread] -> Value
[ToggleChatIsPinned] -> Encoding
[ToggleChatIsPinned] -> Value
[SetChatNotificationSettings] -> Encoding
[SetChatNotificationSettings] -> Value
[SetChatDraftMessage] -> Encoding
[SetChatDraftMessage] -> Value
[SetChatPermissions] -> Encoding
[SetChatPermissions] -> Value
[SetChatPhoto] -> Encoding
[SetChatPhoto] -> Value
[SetChatTitle] -> Encoding
[SetChatTitle] -> Value
[SetChatChatList] -> Encoding
[SetChatChatList] -> Value
[UpgradeBasicGroupChatToSupergroupChat] -> Encoding
[UpgradeBasicGroupChatToSupergroupChat] -> Value
[CreateNewSecretChat] -> Encoding
[CreateNewSecretChat] -> Value
[CreateNewSupergroupChat] -> Encoding
[CreateNewSupergroupChat] -> Value
[CreateNewBasicGroupChat] -> Encoding
[CreateNewBasicGroupChat] -> Value
[CreateSecretChat] -> Encoding
[CreateSecretChat] -> Value
[CreateSupergroupChat] -> Encoding
[CreateSupergroupChat] -> Value
[CreateBasicGroupChat] -> Encoding
[CreateBasicGroupChat] -> Value
[CreatePrivateChat] -> Encoding
[CreatePrivateChat] -> Value
[ReadAllChatMentions] -> Encoding
[ReadAllChatMentions] -> Value
[OpenMessageContent] -> Encoding
[OpenMessageContent] -> Value
[ViewMessages] -> Encoding
[ViewMessages] -> Value
[CloseChat] -> Encoding
[CloseChat] -> Value
[OpenChat] -> Encoding
[OpenChat] -> Value
[SendChatAction] -> Encoding
[SendChatAction] -> Value
[DeleteChatReplyMarkup] -> Encoding
[DeleteChatReplyMarkup] -> Value
[GetInlineGameHighScores] -> Encoding
[GetInlineGameHighScores] -> Value
[GetGameHighScores] -> Encoding
[GetGameHighScores] -> Value
[SetInlineGameScore] -> Encoding
[SetInlineGameScore] -> Value
[SetGameScore] -> Encoding
[SetGameScore] -> Value
[AnswerPreCheckoutQuery] -> Encoding
[AnswerPreCheckoutQuery] -> Value
[AnswerShippingQuery] -> Encoding
[AnswerShippingQuery] -> Value
[AnswerCallbackQuery] -> Encoding
[AnswerCallbackQuery] -> Value
[GetCallbackQueryAnswer] -> Encoding
[GetCallbackQueryAnswer] -> Value
[AnswerInlineQuery] -> Encoding
[AnswerInlineQuery] -> Value
[GetInlineQueryResults] -> Encoding
[GetInlineQueryResults] -> Value
[GetLoginUrl] -> Encoding
[GetLoginUrl] -> Value
[GetLoginUrlInfo] -> Encoding
[GetLoginUrlInfo] -> Value
[StopPoll] -> Encoding
[StopPoll] -> Value
[GetPollVoters] -> Encoding
[GetPollVoters] -> Value
[SetPollAnswer] -> Encoding
[SetPollAnswer] -> Value
[GetJsonString] -> Encoding
[GetJsonString] -> Value
[GetJsonValue] -> Encoding
[GetJsonValue] -> Value
[GetLanguagePackString] -> Encoding
[GetLanguagePackString] -> Value
[CleanFileName] -> Encoding
[CleanFileName] -> Value
[GetFileExtension] -> Encoding
[GetFileExtension] -> Value
[GetFileMimeType] -> Encoding
[GetFileMimeType] -> Value
[GetMarkdownText] -> Encoding
[GetMarkdownText] -> Value
[ParseMarkdown] -> Encoding
[ParseMarkdown] -> Value
[ParseTextEntities] -> Encoding
[ParseTextEntities] -> Value
[GetTextEntities] -> Encoding
[GetTextEntities] -> Value
[EditMessageSchedulingState] -> Encoding
[EditMessageSchedulingState] -> Value
[EditInlineMessageReplyMarkup] -> Encoding
[EditInlineMessageReplyMarkup] -> Value
[EditInlineMessageCaption] -> Encoding
[EditInlineMessageCaption] -> Value
[EditInlineMessageMedia] -> Encoding
[EditInlineMessageMedia] -> Value
[EditInlineMessageLiveLocation] -> Encoding
[EditInlineMessageLiveLocation] -> Value
[EditInlineMessageText] -> Encoding
[EditInlineMessageText] -> Value
[EditMessageReplyMarkup] -> Encoding
[EditMessageReplyMarkup] -> Value
[EditMessageCaption] -> Encoding
[EditMessageCaption] -> Value
[EditMessageMedia] -> Encoding
[EditMessageMedia] -> Value
[EditMessageLiveLocation] -> Encoding
[EditMessageLiveLocation] -> Value
[EditMessageText] -> Encoding
[EditMessageText] -> Value
[DeleteChatMessagesFromUser] -> Encoding
[DeleteChatMessagesFromUser] -> Value
[DeleteMessages] -> Encoding
[DeleteMessages] -> Value
[AddLocalMessage] -> Encoding
[AddLocalMessage] -> Value
[SendChatScreenshotTakenNotification] -> Encoding
[SendChatScreenshotTakenNotification] -> Value
[SendChatSetTtlMessage] -> Encoding
[SendChatSetTtlMessage] -> Value
[ResendMessages] -> Encoding
[ResendMessages] -> Value
[ForwardMessages] -> Encoding
[ForwardMessages] -> Value
[SendInlineQueryResultMessage] -> Encoding
[SendInlineQueryResultMessage] -> Value
[SendBotStartMessage] -> Encoding
[SendBotStartMessage] -> Value
[SendMessageAlbum] -> Encoding
[SendMessageAlbum] -> Value
[SendMessage] -> Encoding
[SendMessage] -> Value
[GetMessageLinkInfo] -> Encoding
[GetMessageLinkInfo] -> Value
[GetMessageLink] -> Encoding
[GetMessageLink] -> Value
[GetPublicMessageLink] -> Encoding
[GetPublicMessageLink] -> Value
[RemoveNotificationGroup] -> Encoding
[RemoveNotificationGroup] -> Value
[RemoveNotification] -> Encoding
[RemoveNotification] -> Value
[GetChatScheduledMessages] -> Encoding
[GetChatScheduledMessages] -> Value
[GetChatMessageCount] -> Encoding
[GetChatMessageCount] -> Value
[GetChatMessageByDate] -> Encoding
[GetChatMessageByDate] -> Value
[GetActiveLiveLocationMessages] -> Encoding
[GetActiveLiveLocationMessages] -> Value
[SearchChatRecentLocationMessages] -> Encoding
[SearchChatRecentLocationMessages] -> Value
[SearchCallMessages] -> Encoding
[SearchCallMessages] -> Value
[SearchSecretMessages] -> Encoding
[SearchSecretMessages] -> Value
[SearchMessages] -> Encoding
[SearchMessages] -> Value
[SearchChatMessages] -> Encoding
[SearchChatMessages] -> Value
[DeleteChatHistory] -> Encoding
[DeleteChatHistory] -> Value
[GetChatHistory] -> Encoding
[GetChatHistory] -> Value
[GetGroupsInCommon] -> Encoding
[GetGroupsInCommon] -> Value
[GetInactiveSupergroupChats] -> Encoding
[GetInactiveSupergroupChats] -> Value
[GetSuitableDiscussionChats] -> Encoding
[GetSuitableDiscussionChats] -> Value
[CheckCreatedPublicChatsLimit] -> Encoding
[CheckCreatedPublicChatsLimit] -> Value
[GetCreatedPublicChats] -> Encoding
[GetCreatedPublicChats] -> Value
[CheckChatUsername] -> Encoding
[CheckChatUsername] -> Value
[ClearRecentlyFoundChats] -> Encoding
[ClearRecentlyFoundChats] -> Value
[RemoveRecentlyFoundChat] -> Encoding
[RemoveRecentlyFoundChat] -> Value
[AddRecentlyFoundChat] -> Encoding
[AddRecentlyFoundChat] -> Value
[RemoveTopChat] -> Encoding
[RemoveTopChat] -> Value
[GetTopChats] -> Encoding
[GetTopChats] -> Value
[SearchChatsNearby] -> Encoding
[SearchChatsNearby] -> Value
[SearchChatsOnServer] -> Encoding
[SearchChatsOnServer] -> Value
[SearchChats] -> Encoding
[SearchChats] -> Value
[SearchPublicChats] -> Encoding
[SearchPublicChats] -> Value
[SearchPublicChat] -> Encoding
[SearchPublicChat] -> Value
[GetChats] -> Encoding
[GetChats] -> Value
[GetRemoteFile] -> Encoding
[GetRemoteFile] -> Value
[GetFile] -> Encoding
[GetFile] -> Value
[GetMessages] -> Encoding
[GetMessages] -> Value
[GetChatPinnedMessage] -> Encoding
[GetChatPinnedMessage] -> Value
[GetRepliedMessage] -> Encoding
[GetRepliedMessage] -> Value
[GetMessageLocally] -> Encoding
[GetMessageLocally] -> Value
[GetMessage] -> Encoding
[GetMessage] -> Value
[GetChat] -> Encoding
[GetChat] -> Value
[GetSecretChat] -> Encoding
[GetSecretChat] -> Value
[GetSupergroupFullInfo] -> Encoding
[GetSupergroupFullInfo] -> Value
[GetSupergroup] -> Encoding
[GetSupergroup] -> Value
[GetBasicGroupFullInfo] -> Encoding
[GetBasicGroupFullInfo] -> Value
[GetBasicGroup] -> Encoding
[GetBasicGroup] -> Value
[GetUserFullInfo] -> Encoding
[GetUserFullInfo] -> Value
[GetUser] -> Encoding
[GetUser] -> Value
[GetMe] -> Encoding
[GetMe] -> Value
[GetTemporaryPasswordState] -> Encoding
[GetTemporaryPasswordState] -> Value
[CreateTemporaryPassword] -> Encoding
[CreateTemporaryPassword] -> Value
[RecoverPassword] -> Encoding
[RecoverPassword] -> Value
[RequestPasswordRecovery] -> Encoding
[RequestPasswordRecovery] -> Value
[ResendRecoveryEmailAddressCode] -> Encoding
[ResendRecoveryEmailAddressCode] -> Value
[CheckRecoveryEmailAddressCode] -> Encoding
[CheckRecoveryEmailAddressCode] -> Value
[SetRecoveryEmailAddress] -> Encoding
[SetRecoveryEmailAddress] -> Value
[GetRecoveryEmailAddress] -> Encoding
[GetRecoveryEmailAddress] -> Value
[SetPassword] -> Encoding
[SetPassword] -> Value
[GetPasswordState] -> Encoding
[GetPasswordState] -> Value
[SetDatabaseEncryptionKey] -> Encoding
[SetDatabaseEncryptionKey] -> Value
[GetCurrentState] -> Encoding
[GetCurrentState] -> Value
[ConfirmQrCodeAuthentication] -> Encoding
[ConfirmQrCodeAuthentication] -> Value
[Destroy] -> Encoding
[Destroy] -> Value
[Close] -> Encoding
[Close] -> Value
[LogOut] -> Encoding
[LogOut] -> Value
[CheckAuthenticationBotToken] -> Encoding
[CheckAuthenticationBotToken] -> Value
[RecoverAuthenticationPassword] -> Encoding
[RecoverAuthenticationPassword] -> Value
[RequestAuthenticationPasswordRecovery] -> Encoding
[RequestAuthenticationPasswordRecovery] -> Value
[CheckAuthenticationPassword] -> Encoding
[CheckAuthenticationPassword] -> Value
[RegisterUser] -> Encoding
[RegisterUser] -> Value
[RequestQrCodeAuthentication] -> Encoding
[RequestQrCodeAuthentication] -> Value
[CheckAuthenticationCode] -> Encoding
[CheckAuthenticationCode] -> Value
[ResendAuthenticationCode] -> Encoding
[ResendAuthenticationCode] -> Value
[SetAuthenticationPhoneNumber] -> Encoding
[SetAuthenticationPhoneNumber] -> Value
[CheckDatabaseEncryptionKey] -> Encoding
[CheckDatabaseEncryptionKey] -> Value
[SetTdlibParameters] -> Encoding
[SetTdlibParameters] -> Value
[GetAuthorizationState] -> Encoding
[GetAuthorizationState] -> Value
Value -> Parser [TestReturnError]
Value -> Parser [TestUseUpdate]
Value -> Parser [TestGetDifference]
Value -> Parser [TestProxy]
Value -> Parser [TestNetwork]
Value -> Parser [TestSquareInt]
Value -> Parser [TestCallVectorStringObject]
Value -> Parser [TestCallVectorString]
Value -> Parser [TestCallVectorIntObject]
Value -> Parser [TestCallVectorInt]
Value -> Parser [TestCallBytes]
Value -> Parser [TestCallString]
Value -> Parser [TestCallEmpty]
Value -> Parser [AddLogMessage]
Value -> Parser [GetLogTagVerbosityLevel]
Value -> Parser [SetLogTagVerbosityLevel]
Value -> Parser [GetLogTags]
Value -> Parser [GetLogVerbosityLevel]
Value -> Parser [SetLogVerbosityLevel]
Value -> Parser [GetLogStream]
Value -> Parser [SetLogStream]
Value -> Parser [PingProxy]
Value -> Parser [GetProxyLink]
Value -> Parser [GetProxies]
Value -> Parser [RemoveProxy]
Value -> Parser [DisableProxy]
Value -> Parser [EnableProxy]
Value -> Parser [EditProxy]
Value -> Parser [AddProxy]
Value -> Parser [SaveApplicationLogEvent]
Value -> Parser [GetApplicationConfig]
Value -> Parser [GetDeepLinkInfo]
Value -> Parser [GetInviteText]
Value -> Parser [GetCountryCode]
Value -> Parser [SetAlarm]
Value -> Parser [AnswerCustomQuery]
Value -> Parser [SendCustomRequest]
Value -> Parser [AcceptTermsOfService]
Value -> Parser [GetMapThumbnailFile]
Value -> Parser [RemoveStickerFromSet]
Value -> Parser [SetStickerPositionInSet]
Value -> Parser [SetStickerSetThumbnail]
Value -> Parser [AddStickerToSet]
Value -> Parser [CreateNewStickerSet]
Value -> Parser [UploadStickerFile]
Value -> Parser [SetBotUpdatesStatus]
Value -> Parser [CheckPhoneNumberConfirmationCode]
Value -> Parser [ResendPhoneNumberConfirmationCode]
Value -> Parser [SendPhoneNumberConfirmationCode]
Value -> Parser [SendPassportAuthorizationForm]
Value -> Parser [GetPassportAuthorizationFormAvailableElements]
Value -> Parser [GetPassportAuthorizationForm]
Value -> Parser [CheckEmailAddressVerificationCode]
Value -> Parser [ResendEmailAddressVerificationCode]
Value -> Parser [SendEmailAddressVerificationCode]
Value -> Parser [CheckPhoneNumberVerificationCode]
Value -> Parser [ResendPhoneNumberVerificationCode]
Value -> Parser [SendPhoneNumberVerificationCode]
Value -> Parser [GetPreferredCountryLanguage]
Value -> Parser [SetPassportElementErrors]
Value -> Parser [DeletePassportElement]
Value -> Parser [SetPassportElement]
Value -> Parser [GetAllPassportElements]
Value -> Parser [GetPassportElement]
Value -> Parser [GetBankCardInfo]
Value -> Parser [SetAutoDownloadSettings]
Value -> Parser [GetAutoDownloadSettingsPresets]
Value -> Parser [ResetNetworkStatistics]
Value -> Parser [AddNetworkStatistics]
Value -> Parser [GetNetworkStatistics]
Value -> Parser [SetNetworkType]
Value -> Parser [OptimizeStorage]
Value -> Parser [GetDatabaseStatistics]
Value -> Parser [GetStorageStatisticsFast]
Value -> Parser [GetStorageStatistics]
Value -> Parser [GetChatStatisticsGraph]
Value -> Parser [GetChatStatistics]
Value -> Parser [GetChatStatisticsUrl]
Value -> Parser [ReportChat]
Value -> Parser [RemoveChatActionBar]
Value -> Parser [DeleteAccount]
Value -> Parser [GetAccountTtl]
Value -> Parser [SetAccountTtl]
Value -> Parser [SetOption]
Value -> Parser [GetOption]
Value -> Parser [GetUserPrivacySettingRules]
Value -> Parser [SetUserPrivacySettingRules]
Value -> Parser [GetRecentlyVisitedTMeUrls]
Value -> Parser [GetPushReceiverId]
Value -> Parser [ProcessPushNotification]
Value -> Parser [RegisterDevice]
Value -> Parser [DeleteLanguagePack]
Value -> Parser [SetCustomLanguagePackString]
Value -> Parser [EditCustomLanguagePackInfo]
Value -> Parser [SetCustomLanguagePack]
Value -> Parser [AddCustomServerLanguagePack]
Value -> Parser [SynchronizeLanguagePack]
Value -> Parser [GetLanguagePackStrings]
Value -> Parser [GetLanguagePackInfo]
Value -> Parser [GetLocalizationTargetInfo]
Value -> Parser [ResetBackgrounds]
Value -> Parser [RemoveBackground]
Value -> Parser [SetBackground]
Value -> Parser [SearchBackground]
Value -> Parser [GetBackgroundUrl]
Value -> Parser [GetBackgrounds]
Value -> Parser [GetSupportUser]
Value -> Parser [DeleteSavedCredentials]
Value -> Parser [DeleteSavedOrderInfo]
Value -> Parser [GetSavedOrderInfo]
Value -> Parser [GetPaymentReceipt]
Value -> Parser [SendPaymentForm]
Value -> Parser [ValidateOrderInfo]
Value -> Parser [GetPaymentForm]
Value -> Parser [GetChatEventLog]
Value -> Parser [CloseSecretChat]
Value -> Parser [DeleteSupergroup]
Value -> Parser [GetSupergroupMembers]
Value -> Parser [ReportSupergroupSpam]
Value -> Parser [ToggleSupergroupIsAllHistoryAvailable]
Value -> Parser [ToggleSupergroupSignMessages]
Value -> Parser [SetSupergroupStickerSet]
Value -> Parser [SetSupergroupUsername]
Value -> Parser [DisconnectAllWebsites]
Value -> Parser [DisconnectWebsite]
Value -> Parser [GetConnectedWebsites]
Value -> Parser [TerminateAllOtherSessions]
Value -> Parser [TerminateSession]
Value -> Parser [GetActiveSessions]
Value -> Parser [SetCommands]
Value -> Parser [CheckChangePhoneNumberCode]
Value -> Parser [ResendChangePhoneNumberCode]
Value -> Parser [ChangePhoneNumber]
Value -> Parser [SetLocation]
Value -> Parser [SetUsername]
Value -> Parser [SetBio]
Value -> Parser [SetName]
Value -> Parser [DeleteProfilePhoto]
Value -> Parser [SetProfilePhoto]
Value -> Parser [GetWebPageInstantView]
Value -> Parser [GetWebPagePreview]
Value -> Parser [RemoveRecentHashtag]
Value -> Parser [SearchHashtags]
Value -> Parser [GetRecentInlineBots]
Value -> Parser [RemoveSavedAnimation]
Value -> Parser [AddSavedAnimation]
Value -> Parser [GetSavedAnimations]
Value -> Parser [GetEmojiSuggestionsUrl]
Value -> Parser [SearchEmojis]
Value -> Parser [GetStickerEmojis]
Value -> Parser [RemoveFavoriteSticker]
Value -> Parser [AddFavoriteSticker]
Value -> Parser [GetFavoriteStickers]
Value -> Parser [ClearRecentStickers]
Value -> Parser [RemoveRecentSticker]
Value -> Parser [AddRecentSticker]
Value -> Parser [GetRecentStickers]
Value -> Parser [ReorderInstalledStickerSets]
Value -> Parser [ViewTrendingStickerSets]
Value -> Parser [ChangeStickerSet]
Value -> Parser [SearchStickerSets]
Value -> Parser [SearchInstalledStickerSets]
Value -> Parser [SearchStickerSet]
Value -> Parser [GetStickerSet]
Value -> Parser [GetAttachedStickerSets]
Value -> Parser [GetTrendingStickerSets]
Value -> Parser [GetArchivedStickerSets]
Value -> Parser [GetInstalledStickerSets]
Value -> Parser [SearchStickers]
Value -> Parser [GetStickers]
Value -> Parser [GetUserProfilePhotos]
Value -> Parser [SharePhoneNumber]
Value -> Parser [ClearImportedContacts]
Value -> Parser [ChangeImportedContacts]
Value -> Parser [GetImportedContactCount]
Value -> Parser [RemoveContacts]
Value -> Parser [SearchContacts]
Value -> Parser [GetContacts]
Value -> Parser [ImportContacts]
Value -> Parser [AddContact]
Value -> Parser [GetBlockedUsers]
Value -> Parser [UnblockUser]
Value -> Parser [BlockUser]
Value -> Parser [SendCallDebugInformation]
Value -> Parser [SendCallRating]
Value -> Parser [DiscardCall]
Value -> Parser [AcceptCall]
Value -> Parser [CreateCall]
Value -> Parser [JoinChatByInviteLink]
Value -> Parser [CheckChatInviteLink]
Value -> Parser [GenerateChatInviteLink]
Value -> Parser [DeleteFile]
Value -> Parser [ReadFilePart]
Value -> Parser [FinishFileGeneration]
Value -> Parser [SetFileGenerationProgress]
Value -> Parser [WriteGeneratedFilePart]
Value -> Parser [CancelUploadFile]
Value -> Parser [UploadFile]
Value -> Parser [CancelDownloadFile]
Value -> Parser [GetFileDownloadedPrefixSize]
Value -> Parser [DownloadFile]
Value -> Parser [SetPinnedChats]
Value -> Parser [ResetAllNotificationSettings]
Value -> Parser [SetScopeNotificationSettings]
Value -> Parser [GetScopeNotificationSettings]
Value -> Parser [GetChatNotificationSettingsExceptions]
Value -> Parser [ClearAllDraftMessages]
Value -> Parser [GetChatAdministrators]
Value -> Parser [SearchChatMembers]
Value -> Parser [GetChatMember]
Value -> Parser [TransferChatOwnership]
Value -> Parser [CanTransferOwnership]
Value -> Parser [SetChatMemberStatus]
Value -> Parser [AddChatMembers]
Value -> Parser [AddChatMember]
Value -> Parser [LeaveChat]
Value -> Parser [JoinChat]
Value -> Parser [UnpinChatMessage]
Value -> Parser [PinChatMessage]
Value -> Parser [SetChatSlowModeDelay]
Value -> Parser [SetChatLocation]
Value -> Parser [SetChatDiscussionGroup]
Value -> Parser [SetChatDescription]
Value -> Parser [SetChatClientData]
Value -> Parser [ToggleChatDefaultDisableNotification]
Value -> Parser [ToggleChatIsMarkedAsUnread]
Value -> Parser [ToggleChatIsPinned]
Value -> Parser [SetChatNotificationSettings]
Value -> Parser [SetChatDraftMessage]
Value -> Parser [SetChatPermissions]
Value -> Parser [SetChatPhoto]
Value -> Parser [SetChatTitle]
Value -> Parser [SetChatChatList]
Value -> Parser [UpgradeBasicGroupChatToSupergroupChat]
Value -> Parser [CreateNewSecretChat]
Value -> Parser [CreateNewSupergroupChat]
Value -> Parser [CreateNewBasicGroupChat]
Value -> Parser [CreateSecretChat]
Value -> Parser [CreateSupergroupChat]
Value -> Parser [CreateBasicGroupChat]
Value -> Parser [CreatePrivateChat]
Value -> Parser [ReadAllChatMentions]
Value -> Parser [OpenMessageContent]
Value -> Parser [ViewMessages]
Value -> Parser [CloseChat]
Value -> Parser [OpenChat]
Value -> Parser [SendChatAction]
Value -> Parser [DeleteChatReplyMarkup]
Value -> Parser [GetInlineGameHighScores]
Value -> Parser [GetGameHighScores]
Value -> Parser [SetInlineGameScore]
Value -> Parser [SetGameScore]
Value -> Parser [AnswerPreCheckoutQuery]
Value -> Parser [AnswerShippingQuery]
Value -> Parser [AnswerCallbackQuery]
Value -> Parser [GetCallbackQueryAnswer]
Value -> Parser [AnswerInlineQuery]
Value -> Parser [GetInlineQueryResults]
Value -> Parser [GetLoginUrl]
Value -> Parser [GetLoginUrlInfo]
Value -> Parser [StopPoll]
Value -> Parser [GetPollVoters]
Value -> Parser [SetPollAnswer]
Value -> Parser [GetJsonString]
Value -> Parser [GetJsonValue]
Value -> Parser [GetLanguagePackString]
Value -> Parser [CleanFileName]
Value -> Parser [GetFileExtension]
Value -> Parser [GetFileMimeType]
Value -> Parser [GetMarkdownText]
Value -> Parser [ParseMarkdown]
Value -> Parser [ParseTextEntities]
Value -> Parser [GetTextEntities]
Value -> Parser [EditMessageSchedulingState]
Value -> Parser [EditInlineMessageReplyMarkup]
Value -> Parser [EditInlineMessageCaption]
Value -> Parser [EditInlineMessageMedia]
Value -> Parser [EditInlineMessageLiveLocation]
Value -> Parser [EditInlineMessageText]
Value -> Parser [EditMessageReplyMarkup]
Value -> Parser [EditMessageCaption]
Value -> Parser [EditMessageMedia]
Value -> Parser [EditMessageLiveLocation]
Value -> Parser [EditMessageText]
Value -> Parser [DeleteChatMessagesFromUser]
Value -> Parser [DeleteMessages]
Value -> Parser [AddLocalMessage]
Value -> Parser [SendChatScreenshotTakenNotification]
Value -> Parser [SendChatSetTtlMessage]
Value -> Parser [ResendMessages]
Value -> Parser [ForwardMessages]
Value -> Parser [SendInlineQueryResultMessage]
Value -> Parser [SendBotStartMessage]
Value -> Parser [SendMessageAlbum]
Value -> Parser [SendMessage]
Value -> Parser [GetMessageLinkInfo]
Value -> Parser [GetMessageLink]
Value -> Parser [GetPublicMessageLink]
Value -> Parser [RemoveNotificationGroup]
Value -> Parser [RemoveNotification]
Value -> Parser [GetChatScheduledMessages]
Value -> Parser [GetChatMessageCount]
Value -> Parser [GetChatMessageByDate]
Value -> Parser [GetActiveLiveLocationMessages]
Value -> Parser [SearchChatRecentLocationMessages]
Value -> Parser [SearchCallMessages]
Value -> Parser [SearchSecretMessages]
Value -> Parser [SearchMessages]
Value -> Parser [SearchChatMessages]
Value -> Parser [DeleteChatHistory]
Value -> Parser [GetChatHistory]
Value -> Parser [GetGroupsInCommon]
Value -> Parser [GetInactiveSupergroupChats]
Value -> Parser [GetSuitableDiscussionChats]
Value -> Parser [CheckCreatedPublicChatsLimit]
Value -> Parser [GetCreatedPublicChats]
Value -> Parser [CheckChatUsername]
Value -> Parser [ClearRecentlyFoundChats]
Value -> Parser [RemoveRecentlyFoundChat]
Value -> Parser [AddRecentlyFoundChat]
Value -> Parser [RemoveTopChat]
Value -> Parser [GetTopChats]
Value -> Parser [SearchChatsNearby]
Value -> Parser [SearchChatsOnServer]
Value -> Parser [SearchChats]
Value -> Parser [SearchPublicChats]
Value -> Parser [SearchPublicChat]
Value -> Parser [GetChats]
Value -> Parser [GetRemoteFile]
Value -> Parser [GetFile]
Value -> Parser [GetMessages]
Value -> Parser [GetChatPinnedMessage]
Value -> Parser [GetRepliedMessage]
Value -> Parser [GetMessageLocally]
Value -> Parser [GetMessage]
Value -> Parser [GetChat]
Value -> Parser [GetSecretChat]
Value -> Parser [GetSupergroupFullInfo]
Value -> Parser [GetSupergroup]
Value -> Parser [GetBasicGroupFullInfo]
Value -> Parser [GetBasicGroup]
Value -> Parser [GetUserFullInfo]
Value -> Parser [GetUser]
Value -> Parser [GetMe]
Value -> Parser [GetTemporaryPasswordState]
Value -> Parser [CreateTemporaryPassword]
Value -> Parser [RecoverPassword]
Value -> Parser [RequestPasswordRecovery]
Value -> Parser [ResendRecoveryEmailAddressCode]
Value -> Parser [CheckRecoveryEmailAddressCode]
Value -> Parser [SetRecoveryEmailAddress]
Value -> Parser [GetRecoveryEmailAddress]
Value -> Parser [SetPassword]
Value -> Parser [GetPasswordState]
Value -> Parser [SetDatabaseEncryptionKey]
Value -> Parser [GetCurrentState]
Value -> Parser [ConfirmQrCodeAuthentication]
Value -> Parser [Destroy]
Value -> Parser [Close]
Value -> Parser [LogOut]
Value -> Parser [CheckAuthenticationBotToken]
Value -> Parser [RecoverAuthenticationPassword]
Value -> Parser [RequestAuthenticationPasswordRecovery]
Value -> Parser [CheckAuthenticationPassword]
Value -> Parser [RegisterUser]
Value -> Parser [RequestQrCodeAuthentication]
Value -> Parser [CheckAuthenticationCode]
Value -> Parser [ResendAuthenticationCode]
Value -> Parser [SetAuthenticationPhoneNumber]
Value -> Parser [CheckDatabaseEncryptionKey]
Value -> Parser [SetTdlibParameters]
Value -> Parser [GetAuthorizationState]
Value -> Parser TestReturnError
Value -> Parser TestUseUpdate
Value -> Parser TestGetDifference
Value -> Parser TestProxy
Value -> Parser TestNetwork
Value -> Parser TestSquareInt
Value -> Parser TestCallVectorStringObject
Value -> Parser TestCallVectorString
Value -> Parser TestCallVectorIntObject
Value -> Parser TestCallVectorInt
Value -> Parser TestCallBytes
Value -> Parser TestCallString
Value -> Parser TestCallEmpty
Value -> Parser AddLogMessage
Value -> Parser GetLogTagVerbosityLevel
Value -> Parser SetLogTagVerbosityLevel
Value -> Parser GetLogTags
Value -> Parser GetLogVerbosityLevel
Value -> Parser SetLogVerbosityLevel
Value -> Parser GetLogStream
Value -> Parser SetLogStream
Value -> Parser PingProxy
Value -> Parser GetProxyLink
Value -> Parser GetProxies
Value -> Parser RemoveProxy
Value -> Parser DisableProxy
Value -> Parser EnableProxy
Value -> Parser EditProxy
Value -> Parser AddProxy
Value -> Parser SaveApplicationLogEvent
Value -> Parser GetApplicationConfig
Value -> Parser GetDeepLinkInfo
Value -> Parser GetInviteText
Value -> Parser GetCountryCode
Value -> Parser SetAlarm
Value -> Parser AnswerCustomQuery
Value -> Parser SendCustomRequest
Value -> Parser AcceptTermsOfService
Value -> Parser GetMapThumbnailFile
Value -> Parser RemoveStickerFromSet
Value -> Parser SetStickerPositionInSet
Value -> Parser SetStickerSetThumbnail
Value -> Parser AddStickerToSet
Value -> Parser CreateNewStickerSet
Value -> Parser UploadStickerFile
Value -> Parser SetBotUpdatesStatus
Value -> Parser CheckPhoneNumberConfirmationCode
Value -> Parser ResendPhoneNumberConfirmationCode
Value -> Parser SendPhoneNumberConfirmationCode
Value -> Parser SendPassportAuthorizationForm
Value -> Parser GetPassportAuthorizationFormAvailableElements
Value -> Parser GetPassportAuthorizationForm
Value -> Parser CheckEmailAddressVerificationCode
Value -> Parser ResendEmailAddressVerificationCode
Value -> Parser SendEmailAddressVerificationCode
Value -> Parser CheckPhoneNumberVerificationCode
Value -> Parser ResendPhoneNumberVerificationCode
Value -> Parser SendPhoneNumberVerificationCode
Value -> Parser GetPreferredCountryLanguage
Value -> Parser SetPassportElementErrors
Value -> Parser DeletePassportElement
Value -> Parser SetPassportElement
Value -> Parser GetAllPassportElements
Value -> Parser GetPassportElement
Value -> Parser GetBankCardInfo
Value -> Parser SetAutoDownloadSettings
Value -> Parser GetAutoDownloadSettingsPresets
Value -> Parser ResetNetworkStatistics
Value -> Parser AddNetworkStatistics
Value -> Parser GetNetworkStatistics
Value -> Parser SetNetworkType
Value -> Parser OptimizeStorage
Value -> Parser GetDatabaseStatistics
Value -> Parser GetStorageStatisticsFast
Value -> Parser GetStorageStatistics
Value -> Parser GetChatStatisticsGraph
Value -> Parser GetChatStatistics
Value -> Parser GetChatStatisticsUrl
Value -> Parser ReportChat
Value -> Parser RemoveChatActionBar
Value -> Parser DeleteAccount
Value -> Parser GetAccountTtl
Value -> Parser SetAccountTtl
Value -> Parser SetOption
Value -> Parser GetOption
Value -> Parser GetUserPrivacySettingRules
Value -> Parser SetUserPrivacySettingRules
Value -> Parser GetRecentlyVisitedTMeUrls
Value -> Parser GetPushReceiverId
Value -> Parser ProcessPushNotification
Value -> Parser RegisterDevice
Value -> Parser DeleteLanguagePack
Value -> Parser SetCustomLanguagePackString
Value -> Parser EditCustomLanguagePackInfo
Value -> Parser SetCustomLanguagePack
Value -> Parser AddCustomServerLanguagePack
Value -> Parser SynchronizeLanguagePack
Value -> Parser GetLanguagePackStrings
Value -> Parser GetLanguagePackInfo
Value -> Parser GetLocalizationTargetInfo
Value -> Parser ResetBackgrounds
Value -> Parser RemoveBackground
Value -> Parser SetBackground
Value -> Parser SearchBackground
Value -> Parser GetBackgroundUrl
Value -> Parser GetBackgrounds
Value -> Parser GetSupportUser
Value -> Parser DeleteSavedCredentials
Value -> Parser DeleteSavedOrderInfo
Value -> Parser GetSavedOrderInfo
Value -> Parser GetPaymentReceipt
Value -> Parser SendPaymentForm
Value -> Parser ValidateOrderInfo
Value -> Parser GetPaymentForm
Value -> Parser GetChatEventLog
Value -> Parser CloseSecretChat
Value -> Parser DeleteSupergroup
Value -> Parser GetSupergroupMembers
Value -> Parser ReportSupergroupSpam
Value -> Parser ToggleSupergroupIsAllHistoryAvailable
Value -> Parser ToggleSupergroupSignMessages
Value -> Parser SetSupergroupStickerSet
Value -> Parser SetSupergroupUsername
Value -> Parser DisconnectAllWebsites
Value -> Parser DisconnectWebsite
Value -> Parser GetConnectedWebsites
Value -> Parser TerminateAllOtherSessions
Value -> Parser TerminateSession
Value -> Parser GetActiveSessions
Value -> Parser SetCommands
Value -> Parser CheckChangePhoneNumberCode
Value -> Parser ResendChangePhoneNumberCode
Value -> Parser ChangePhoneNumber
Value -> Parser SetLocation
Value -> Parser SetUsername
Value -> Parser SetBio
Value -> Parser SetName
Value -> Parser DeleteProfilePhoto
Value -> Parser SetProfilePhoto
Value -> Parser GetWebPageInstantView
Value -> Parser GetWebPagePreview
Value -> Parser RemoveRecentHashtag
Value -> Parser SearchHashtags
Value -> Parser GetRecentInlineBots
Value -> Parser RemoveSavedAnimation
Value -> Parser AddSavedAnimation
Value -> Parser GetSavedAnimations
Value -> Parser GetEmojiSuggestionsUrl
Value -> Parser SearchEmojis
Value -> Parser GetStickerEmojis
Value -> Parser RemoveFavoriteSticker
Value -> Parser AddFavoriteSticker
Value -> Parser GetFavoriteStickers
Value -> Parser ClearRecentStickers
Value -> Parser RemoveRecentSticker
Value -> Parser AddRecentSticker
Value -> Parser GetRecentStickers
Value -> Parser ReorderInstalledStickerSets
Value -> Parser ViewTrendingStickerSets
Value -> Parser ChangeStickerSet
Value -> Parser SearchStickerSets
Value -> Parser SearchInstalledStickerSets
Value -> Parser SearchStickerSet
Value -> Parser GetStickerSet
Value -> Parser GetAttachedStickerSets
Value -> Parser GetTrendingStickerSets
Value -> Parser GetArchivedStickerSets
Value -> Parser GetInstalledStickerSets
Value -> Parser SearchStickers
Value -> Parser GetStickers
Value -> Parser GetUserProfilePhotos
Value -> Parser SharePhoneNumber
Value -> Parser ClearImportedContacts
Value -> Parser ChangeImportedContacts
Value -> Parser GetImportedContactCount
Value -> Parser RemoveContacts
Value -> Parser SearchContacts
Value -> Parser GetContacts
Value -> Parser ImportContacts
Value -> Parser AddContact
Value -> Parser GetBlockedUsers
Value -> Parser UnblockUser
Value -> Parser BlockUser
Value -> Parser SendCallDebugInformation
Value -> Parser SendCallRating
Value -> Parser DiscardCall
Value -> Parser AcceptCall
Value -> Parser CreateCall
Value -> Parser JoinChatByInviteLink
Value -> Parser CheckChatInviteLink
Value -> Parser GenerateChatInviteLink
Value -> Parser DeleteFile
Value -> Parser ReadFilePart
Value -> Parser FinishFileGeneration
Value -> Parser SetFileGenerationProgress
Value -> Parser WriteGeneratedFilePart
Value -> Parser CancelUploadFile
Value -> Parser UploadFile
Value -> Parser CancelDownloadFile
Value -> Parser GetFileDownloadedPrefixSize
Value -> Parser DownloadFile
Value -> Parser SetPinnedChats
Value -> Parser ResetAllNotificationSettings
Value -> Parser SetScopeNotificationSettings
Value -> Parser GetScopeNotificationSettings
Value -> Parser GetChatNotificationSettingsExceptions
Value -> Parser ClearAllDraftMessages
Value -> Parser GetChatAdministrators
Value -> Parser SearchChatMembers
Value -> Parser GetChatMember
Value -> Parser TransferChatOwnership
Value -> Parser CanTransferOwnership
Value -> Parser SetChatMemberStatus
Value -> Parser AddChatMembers
Value -> Parser AddChatMember
Value -> Parser LeaveChat
Value -> Parser JoinChat
Value -> Parser UnpinChatMessage
Value -> Parser PinChatMessage
Value -> Parser SetChatSlowModeDelay
Value -> Parser SetChatLocation
Value -> Parser SetChatDiscussionGroup
Value -> Parser SetChatDescription
Value -> Parser SetChatClientData
Value -> Parser ToggleChatDefaultDisableNotification
Value -> Parser ToggleChatIsMarkedAsUnread
Value -> Parser ToggleChatIsPinned
Value -> Parser SetChatNotificationSettings
Value -> Parser SetChatDraftMessage
Value -> Parser SetChatPermissions
Value -> Parser SetChatPhoto
Value -> Parser SetChatTitle
Value -> Parser SetChatChatList
Value -> Parser UpgradeBasicGroupChatToSupergroupChat
Value -> Parser CreateNewSecretChat
Value -> Parser CreateNewSupergroupChat
Value -> Parser CreateNewBasicGroupChat
Value -> Parser CreateSecretChat
Value -> Parser CreateSupergroupChat
Value -> Parser CreateBasicGroupChat
Value -> Parser CreatePrivateChat
Value -> Parser ReadAllChatMentions
Value -> Parser OpenMessageContent
Value -> Parser ViewMessages
Value -> Parser CloseChat
Value -> Parser OpenChat
Value -> Parser SendChatAction
Value -> Parser DeleteChatReplyMarkup
Value -> Parser GetInlineGameHighScores
Value -> Parser GetGameHighScores
Value -> Parser SetInlineGameScore
Value -> Parser SetGameScore
Value -> Parser AnswerPreCheckoutQuery
Value -> Parser AnswerShippingQuery
Value -> Parser AnswerCallbackQuery
Value -> Parser GetCallbackQueryAnswer
Value -> Parser AnswerInlineQuery
Value -> Parser GetInlineQueryResults
Value -> Parser GetLoginUrl
Value -> Parser GetLoginUrlInfo
Value -> Parser StopPoll
Value -> Parser GetPollVoters
Value -> Parser SetPollAnswer
Value -> Parser GetJsonString
Value -> Parser GetJsonValue
Value -> Parser GetLanguagePackString
Value -> Parser CleanFileName
Value -> Parser GetFileExtension
Value -> Parser GetFileMimeType
Value -> Parser GetMarkdownText
Value -> Parser ParseMarkdown
Value -> Parser ParseTextEntities
Value -> Parser GetTextEntities
Value -> Parser EditMessageSchedulingState
Value -> Parser EditInlineMessageReplyMarkup
Value -> Parser EditInlineMessageCaption
Value -> Parser EditInlineMessageMedia
Value -> Parser EditInlineMessageLiveLocation
Value -> Parser EditInlineMessageText
Value -> Parser EditMessageReplyMarkup
Value -> Parser EditMessageCaption
Value -> Parser EditMessageMedia
Value -> Parser EditMessageLiveLocation
Value -> Parser EditMessageText
Value -> Parser DeleteChatMessagesFromUser
Value -> Parser DeleteMessages
Value -> Parser AddLocalMessage
Value -> Parser SendChatScreenshotTakenNotification
Value -> Parser SendChatSetTtlMessage
Value -> Parser ResendMessages
Value -> Parser ForwardMessages
Value -> Parser SendInlineQueryResultMessage
Value -> Parser SendBotStartMessage
Value -> Parser SendMessageAlbum
Value -> Parser SendMessage
Value -> Parser GetMessageLinkInfo
Value -> Parser GetMessageLink
Value -> Parser GetPublicMessageLink
Value -> Parser RemoveNotificationGroup
Value -> Parser RemoveNotification
Value -> Parser GetChatScheduledMessages
Value -> Parser GetChatMessageCount
Value -> Parser GetChatMessageByDate
Value -> Parser GetActiveLiveLocationMessages
Value -> Parser SearchChatRecentLocationMessages
Value -> Parser SearchCallMessages
Value -> Parser SearchSecretMessages
Value -> Parser SearchMessages
Value -> Parser SearchChatMessages
Value -> Parser DeleteChatHistory
Value -> Parser GetChatHistory
Value -> Parser GetGroupsInCommon
Value -> Parser GetInactiveSupergroupChats
Value -> Parser GetSuitableDiscussionChats
Value -> Parser CheckCreatedPublicChatsLimit
Value -> Parser GetCreatedPublicChats
Value -> Parser CheckChatUsername
Value -> Parser ClearRecentlyFoundChats
Value -> Parser RemoveRecentlyFoundChat
Value -> Parser AddRecentlyFoundChat
Value -> Parser RemoveTopChat
Value -> Parser GetTopChats
Value -> Parser SearchChatsNearby
Value -> Parser SearchChatsOnServer
Value -> Parser SearchChats
Value -> Parser SearchPublicChats
Value -> Parser SearchPublicChat
Value -> Parser GetChats
Value -> Parser GetRemoteFile
Value -> Parser GetFile
Value -> Parser GetMessages
Value -> Parser GetChatPinnedMessage
Value -> Parser GetRepliedMessage
Value -> Parser GetMessageLocally
Value -> Parser GetMessage
Value -> Parser GetChat
Value -> Parser GetSecretChat
Value -> Parser GetSupergroupFullInfo
Value -> Parser GetSupergroup
Value -> Parser GetBasicGroupFullInfo
Value -> Parser GetBasicGroup
Value -> Parser GetUserFullInfo
Value -> Parser GetUser
Value -> Parser GetMe
Value -> Parser GetTemporaryPasswordState
Value -> Parser CreateTemporaryPassword
Value -> Parser RecoverPassword
Value -> Parser RequestPasswordRecovery
Value -> Parser ResendRecoveryEmailAddressCode
Value -> Parser CheckRecoveryEmailAddressCode
Value -> Parser SetRecoveryEmailAddress
Value -> Parser GetRecoveryEmailAddress
Value -> Parser SetPassword
Value -> Parser GetPasswordState
Value -> Parser SetDatabaseEncryptionKey
Value -> Parser GetCurrentState
Value -> Parser ConfirmQrCodeAuthentication
Value -> Parser Destroy
Value -> Parser Close
Value -> Parser LogOut
Value -> Parser CheckAuthenticationBotToken
Value -> Parser RecoverAuthenticationPassword
Value -> Parser RequestAuthenticationPasswordRecovery
Value -> Parser CheckAuthenticationPassword
Value -> Parser RegisterUser
Value -> Parser RequestQrCodeAuthentication
Value -> Parser CheckAuthenticationCode
Value -> Parser ResendAuthenticationCode
Value -> Parser SetAuthenticationPhoneNumber
Value -> Parser CheckDatabaseEncryptionKey
Value -> Parser SetTdlibParameters
Value -> Parser GetAuthorizationState
TestReturnError -> Encoding
TestReturnError -> Value
TestUseUpdate -> Encoding
TestUseUpdate -> Value
TestGetDifference -> Encoding
TestGetDifference -> Value
TestProxy -> Encoding
TestProxy -> Value
TestNetwork -> Encoding
TestNetwork -> Value
TestSquareInt -> Encoding
TestSquareInt -> Value
TestCallVectorStringObject -> Encoding
TestCallVectorStringObject -> Value
TestCallVectorString -> Encoding
TestCallVectorString -> Value
TestCallVectorIntObject -> Encoding
TestCallVectorIntObject -> Value
TestCallVectorInt -> Encoding
TestCallVectorInt -> Value
TestCallBytes -> Encoding
TestCallBytes -> Value
TestCallString -> Encoding
TestCallString -> Value
TestCallEmpty -> Encoding
TestCallEmpty -> Value
AddLogMessage -> Encoding
AddLogMessage -> Value
GetLogTagVerbosityLevel -> Encoding
GetLogTagVerbosityLevel -> Value
SetLogTagVerbosityLevel -> Encoding
SetLogTagVerbosityLevel -> Value
GetLogTags -> Encoding
GetLogTags -> Value
GetLogVerbosityLevel -> Encoding
GetLogVerbosityLevel -> Value
SetLogVerbosityLevel -> Encoding
SetLogVerbosityLevel -> Value
GetLogStream -> Encoding
GetLogStream -> Value
SetLogStream -> Encoding
SetLogStream -> Value
PingProxy -> Encoding
PingProxy -> Value
GetProxyLink -> Encoding
GetProxyLink -> Value
GetProxies -> Encoding
GetProxies -> Value
RemoveProxy -> Encoding
RemoveProxy -> Value
DisableProxy -> Encoding
DisableProxy -> Value
EnableProxy -> Encoding
EnableProxy -> Value
EditProxy -> Encoding
EditProxy -> Value
AddProxy -> Encoding
AddProxy -> Value
SaveApplicationLogEvent -> Encoding
SaveApplicationLogEvent -> Value
GetApplicationConfig -> Encoding
GetApplicationConfig -> Value
GetDeepLinkInfo -> Encoding
GetDeepLinkInfo -> Value
GetInviteText -> Encoding
GetInviteText -> Value
GetCountryCode -> Encoding
GetCountryCode -> Value
SetAlarm -> Encoding
SetAlarm -> Value
AnswerCustomQuery -> Encoding
AnswerCustomQuery -> Value
SendCustomRequest -> Encoding
SendCustomRequest -> Value
AcceptTermsOfService -> Encoding
AcceptTermsOfService -> Value
GetMapThumbnailFile -> Encoding
GetMapThumbnailFile -> Value
RemoveStickerFromSet -> Encoding
RemoveStickerFromSet -> Value
SetStickerPositionInSet -> Encoding
SetStickerPositionInSet -> Value
SetStickerSetThumbnail -> Encoding
SetStickerSetThumbnail -> Value
AddStickerToSet -> Encoding
AddStickerToSet -> Value
CreateNewStickerSet -> Encoding
CreateNewStickerSet -> Value
UploadStickerFile -> Encoding
UploadStickerFile -> Value
SetBotUpdatesStatus -> Encoding
SetBotUpdatesStatus -> Value
CheckPhoneNumberConfirmationCode -> Encoding
CheckPhoneNumberConfirmationCode -> Value
ResendPhoneNumberConfirmationCode -> Encoding
ResendPhoneNumberConfirmationCode -> Value
SendPhoneNumberConfirmationCode -> Encoding
SendPhoneNumberConfirmationCode -> Value
SendPassportAuthorizationForm -> Encoding
SendPassportAuthorizationForm -> Value
GetPassportAuthorizationFormAvailableElements -> Encoding
GetPassportAuthorizationFormAvailableElements -> Value
GetPassportAuthorizationForm -> Encoding
GetPassportAuthorizationForm -> Value
CheckEmailAddressVerificationCode -> Encoding
CheckEmailAddressVerificationCode -> Value
ResendEmailAddressVerificationCode -> Encoding
ResendEmailAddressVerificationCode -> Value
SendEmailAddressVerificationCode -> Encoding
SendEmailAddressVerificationCode -> Value
CheckPhoneNumberVerificationCode -> Encoding
CheckPhoneNumberVerificationCode -> Value
ResendPhoneNumberVerificationCode -> Encoding
ResendPhoneNumberVerificationCode -> Value
SendPhoneNumberVerificationCode -> Encoding
SendPhoneNumberVerificationCode -> Value
GetPreferredCountryLanguage -> Encoding
GetPreferredCountryLanguage -> Value
SetPassportElementErrors -> Encoding
SetPassportElementErrors -> Value
DeletePassportElement -> Encoding
DeletePassportElement -> Value
SetPassportElement -> Encoding
SetPassportElement -> Value
GetAllPassportElements -> Encoding
GetAllPassportElements -> Value
GetPassportElement -> Encoding
GetPassportElement -> Value
GetBankCardInfo -> Encoding
GetBankCardInfo -> Value
SetAutoDownloadSettings -> Encoding
SetAutoDownloadSettings -> Value
GetAutoDownloadSettingsPresets -> Encoding
GetAutoDownloadSettingsPresets -> Value
ResetNetworkStatistics -> Encoding
ResetNetworkStatistics -> Value
AddNetworkStatistics -> Encoding
AddNetworkStatistics -> Value
GetNetworkStatistics -> Encoding
GetNetworkStatistics -> Value
SetNetworkType -> Encoding
SetNetworkType -> Value
OptimizeStorage -> Encoding
OptimizeStorage -> Value
GetDatabaseStatistics -> Encoding
GetDatabaseStatistics -> Value
GetStorageStatisticsFast -> Encoding
GetStorageStatisticsFast -> Value
GetStorageStatistics -> Encoding
GetStorageStatistics -> Value
GetChatStatisticsGraph -> Encoding
GetChatStatisticsGraph -> Value
GetChatStatistics -> Encoding
GetChatStatistics -> Value
GetChatStatisticsUrl -> Encoding
GetChatStatisticsUrl -> Value
ReportChat -> Encoding
ReportChat -> Value
RemoveChatActionBar -> Encoding
RemoveChatActionBar -> Value
DeleteAccount -> Encoding
DeleteAccount -> Value
GetAccountTtl -> Encoding
GetAccountTtl -> Value
SetAccountTtl -> Encoding
SetAccountTtl -> Value
SetOption -> Encoding
SetOption -> Value
GetOption -> Encoding
GetOption -> Value
GetUserPrivacySettingRules -> Encoding
GetUserPrivacySettingRules -> Value
SetUserPrivacySettingRules -> Encoding
SetUserPrivacySettingRules -> Value
GetRecentlyVisitedTMeUrls -> Encoding
GetRecentlyVisitedTMeUrls -> Value
GetPushReceiverId -> Encoding
GetPushReceiverId -> Value
ProcessPushNotification -> Encoding
ProcessPushNotification -> Value
RegisterDevice -> Encoding
RegisterDevice -> Value
DeleteLanguagePack -> Encoding
DeleteLanguagePack -> Value
SetCustomLanguagePackString -> Encoding
SetCustomLanguagePackString -> Value
EditCustomLanguagePackInfo -> Encoding
EditCustomLanguagePackInfo -> Value
SetCustomLanguagePack -> Encoding
SetCustomLanguagePack -> Value
AddCustomServerLanguagePack -> Encoding
AddCustomServerLanguagePack -> Value
SynchronizeLanguagePack -> Encoding
SynchronizeLanguagePack -> Value
GetLanguagePackStrings -> Encoding
GetLanguagePackStrings -> Value
GetLanguagePackInfo -> Encoding
GetLanguagePackInfo -> Value
GetLocalizationTargetInfo -> Encoding
GetLocalizationTargetInfo -> Value
ResetBackgrounds -> Encoding
ResetBackgrounds -> Value
RemoveBackground -> Encoding
RemoveBackground -> Value
SetBackground -> Encoding
SetBackground -> Value
SearchBackground -> Encoding
SearchBackground -> Value
GetBackgroundUrl -> Encoding
GetBackgroundUrl -> Value
GetBackgrounds -> Encoding
GetBackgrounds -> Value
GetSupportUser -> Encoding
GetSupportUser -> Value
DeleteSavedCredentials -> Encoding
DeleteSavedCredentials -> Value
DeleteSavedOrderInfo -> Encoding
DeleteSavedOrderInfo -> Value
GetSavedOrderInfo -> Encoding
GetSavedOrderInfo -> Value
GetPaymentReceipt -> Encoding
GetPaymentReceipt -> Value
SendPaymentForm -> Encoding
SendPaymentForm -> Value
ValidateOrderInfo -> Encoding
ValidateOrderInfo -> Value
GetPaymentForm -> Encoding
GetPaymentForm -> Value
GetChatEventLog -> Encoding
GetChatEventLog -> Value
CloseSecretChat -> Encoding
CloseSecretChat -> Value
DeleteSupergroup -> Encoding
DeleteSupergroup -> Value
GetSupergroupMembers -> Encoding
GetSupergroupMembers -> Value
ReportSupergroupSpam -> Encoding
ReportSupergroupSpam -> Value
ToggleSupergroupIsAllHistoryAvailable -> Encoding
ToggleSupergroupIsAllHistoryAvailable -> Value
ToggleSupergroupSignMessages -> Encoding
ToggleSupergroupSignMessages -> Value
SetSupergroupStickerSet -> Encoding
SetSupergroupStickerSet -> Value
SetSupergroupUsername -> Encoding
SetSupergroupUsername -> Value
DisconnectAllWebsites -> Encoding
DisconnectAllWebsites -> Value
DisconnectWebsite -> Encoding
DisconnectWebsite -> Value
GetConnectedWebsites -> Encoding
GetConnectedWebsites -> Value
TerminateAllOtherSessions -> Encoding
TerminateAllOtherSessions -> Value
TerminateSession -> Encoding
TerminateSession -> Value
GetActiveSessions -> Encoding
GetActiveSessions -> Value
SetCommands -> Encoding
SetCommands -> Value
CheckChangePhoneNumberCode -> Encoding
CheckChangePhoneNumberCode -> Value
ResendChangePhoneNumberCode -> Encoding
ResendChangePhoneNumberCode -> Value
ChangePhoneNumber -> Encoding
ChangePhoneNumber -> Value
SetLocation -> Encoding
SetLocation -> Value
SetUsername -> Encoding
SetUsername -> Value
SetBio -> Encoding
SetBio -> Value
SetName -> Encoding
SetName -> Value
DeleteProfilePhoto -> Encoding
DeleteProfilePhoto -> Value
SetProfilePhoto -> Encoding
SetProfilePhoto -> Value
GetWebPageInstantView -> Encoding
GetWebPageInstantView -> Value
GetWebPagePreview -> Encoding
GetWebPagePreview -> Value
RemoveRecentHashtag -> Encoding
RemoveRecentHashtag -> Value
SearchHashtags -> Encoding
SearchHashtags -> Value
GetRecentInlineBots -> Encoding
GetRecentInlineBots -> Value
RemoveSavedAnimation -> Encoding
RemoveSavedAnimation -> Value
AddSavedAnimation -> Encoding
AddSavedAnimation -> Value
GetSavedAnimations -> Encoding
GetSavedAnimations -> Value
GetEmojiSuggestionsUrl -> Encoding
GetEmojiSuggestionsUrl -> Value
SearchEmojis -> Encoding
SearchEmojis -> Value
GetStickerEmojis -> Encoding
GetStickerEmojis -> Value
RemoveFavoriteSticker -> Encoding
RemoveFavoriteSticker -> Value
AddFavoriteSticker -> Encoding
AddFavoriteSticker -> Value
GetFavoriteStickers -> Encoding
GetFavoriteStickers -> Value
ClearRecentStickers -> Encoding
ClearRecentStickers -> Value
RemoveRecentSticker -> Encoding
RemoveRecentSticker -> Value
AddRecentSticker -> Encoding
AddRecentSticker -> Value
GetRecentStickers -> Encoding
GetRecentStickers -> Value
ReorderInstalledStickerSets -> Encoding
ReorderInstalledStickerSets -> Value
ViewTrendingStickerSets -> Encoding
ViewTrendingStickerSets -> Value
ChangeStickerSet -> Encoding
ChangeStickerSet -> Value
SearchStickerSets -> Encoding
SearchStickerSets -> Value
SearchInstalledStickerSets -> Encoding
SearchInstalledStickerSets -> Value
SearchStickerSet -> Encoding
SearchStickerSet -> Value
GetStickerSet -> Encoding
GetStickerSet -> Value
GetAttachedStickerSets -> Encoding
GetAttachedStickerSets -> Value
GetTrendingStickerSets -> Encoding
GetTrendingStickerSets -> Value
GetArchivedStickerSets -> Encoding
GetArchivedStickerSets -> Value
GetInstalledStickerSets -> Encoding
GetInstalledStickerSets -> Value
SearchStickers -> Encoding
SearchStickers -> Value
GetStickers -> Encoding
GetStickers -> Value
GetUserProfilePhotos -> Encoding
GetUserProfilePhotos -> Value
SharePhoneNumber -> Encoding
SharePhoneNumber -> Value
ClearImportedContacts -> Encoding
ClearImportedContacts -> Value
ChangeImportedContacts -> Encoding
ChangeImportedContacts -> Value
GetImportedContactCount -> Encoding
GetImportedContactCount -> Value
RemoveContacts -> Encoding
RemoveContacts -> Value
SearchContacts -> Encoding
SearchContacts -> Value
GetContacts -> Encoding
GetContacts -> Value
ImportContacts -> Encoding
ImportContacts -> Value
AddContact -> Encoding
AddContact -> Value
GetBlockedUsers -> Encoding
GetBlockedUsers -> Value
UnblockUser -> Encoding
UnblockUser -> Value
BlockUser -> Encoding
BlockUser -> Value
SendCallDebugInformation -> Encoding
SendCallDebugInformation -> Value
SendCallRating -> Encoding
SendCallRating -> Value
DiscardCall -> Encoding
DiscardCall -> Value
AcceptCall -> Encoding
AcceptCall -> Value
CreateCall -> Encoding
CreateCall -> Value
JoinChatByInviteLink -> Encoding
JoinChatByInviteLink -> Value
CheckChatInviteLink -> Encoding
CheckChatInviteLink -> Value
GenerateChatInviteLink -> Encoding
GenerateChatInviteLink -> Value
DeleteFile -> Encoding
DeleteFile -> Value
ReadFilePart -> Encoding
ReadFilePart -> Value
FinishFileGeneration -> Encoding
FinishFileGeneration -> Value
SetFileGenerationProgress -> Encoding
SetFileGenerationProgress -> Value
WriteGeneratedFilePart -> Encoding
WriteGeneratedFilePart -> Value
CancelUploadFile -> Encoding
CancelUploadFile -> Value
UploadFile -> Encoding
UploadFile -> Value
CancelDownloadFile -> Encoding
CancelDownloadFile -> Value
GetFileDownloadedPrefixSize -> Encoding
GetFileDownloadedPrefixSize -> Value
DownloadFile -> Encoding
DownloadFile -> Value
SetPinnedChats -> Encoding
SetPinnedChats -> Value
ResetAllNotificationSettings -> Encoding
ResetAllNotificationSettings -> Value
SetScopeNotificationSettings -> Encoding
SetScopeNotificationSettings -> Value
GetScopeNotificationSettings -> Encoding
GetScopeNotificationSettings -> Value
GetChatNotificationSettingsExceptions -> Encoding
GetChatNotificationSettingsExceptions -> Value
ClearAllDraftMessages -> Encoding
ClearAllDraftMessages -> Value
GetChatAdministrators -> Encoding
GetChatAdministrators -> Value
SearchChatMembers -> Encoding
SearchChatMembers -> Value
GetChatMember -> Encoding
GetChatMember -> Value
TransferChatOwnership -> Encoding
TransferChatOwnership -> Value
CanTransferOwnership -> Encoding
CanTransferOwnership -> Value
SetChatMemberStatus -> Encoding
SetChatMemberStatus -> Value
AddChatMembers -> Encoding
AddChatMembers -> Value
AddChatMember -> Encoding
AddChatMember -> Value
LeaveChat -> Encoding
LeaveChat -> Value
JoinChat -> Encoding
JoinChat -> Value
UnpinChatMessage -> Encoding
UnpinChatMessage -> Value
PinChatMessage -> Encoding
PinChatMessage -> Value
SetChatSlowModeDelay -> Encoding
SetChatSlowModeDelay -> Value
SetChatLocation -> Encoding
SetChatLocation -> Value
SetChatDiscussionGroup -> Encoding
SetChatDiscussionGroup -> Value
SetChatDescription -> Encoding
SetChatDescription -> Value
SetChatClientData -> Encoding
SetChatClientData -> Value
ToggleChatDefaultDisableNotification -> Encoding
ToggleChatDefaultDisableNotification -> Value
ToggleChatIsMarkedAsUnread -> Encoding
ToggleChatIsMarkedAsUnread -> Value
ToggleChatIsPinned -> Encoding
ToggleChatIsPinned -> Value
SetChatNotificationSettings -> Encoding
SetChatNotificationSettings -> Value
SetChatDraftMessage -> Encoding
SetChatDraftMessage -> Value
SetChatPermissions -> Encoding
SetChatPermissions -> Value
SetChatPhoto -> Encoding
SetChatPhoto -> Value
SetChatTitle -> Encoding
SetChatTitle -> Value
SetChatChatList -> Encoding
SetChatChatList -> Value
UpgradeBasicGroupChatToSupergroupChat -> Encoding
UpgradeBasicGroupChatToSupergroupChat -> Value
CreateNewSecretChat -> Encoding
CreateNewSecretChat -> Value
CreateNewSupergroupChat -> Encoding
CreateNewSupergroupChat -> Value
CreateNewBasicGroupChat -> Encoding
CreateNewBasicGroupChat -> Value
CreateSecretChat -> Encoding
CreateSecretChat -> Value
CreateSupergroupChat -> Encoding
CreateSupergroupChat -> Value
CreateBasicGroupChat -> Encoding
CreateBasicGroupChat -> Value
CreatePrivateChat -> Encoding
CreatePrivateChat -> Value
ReadAllChatMentions -> Encoding
ReadAllChatMentions -> Value
OpenMessageContent -> Encoding
OpenMessageContent -> Value
ViewMessages -> Encoding
ViewMessages -> Value
CloseChat -> Encoding
CloseChat -> Value
OpenChat -> Encoding
OpenChat -> Value
SendChatAction -> Encoding
SendChatAction -> Value
DeleteChatReplyMarkup -> Encoding
DeleteChatReplyMarkup -> Value
GetInlineGameHighScores -> Encoding
GetInlineGameHighScores -> Value
GetGameHighScores -> Encoding
GetGameHighScores -> Value
SetInlineGameScore -> Encoding
SetInlineGameScore -> Value
SetGameScore -> Encoding
SetGameScore -> Value
AnswerPreCheckoutQuery -> Encoding
AnswerPreCheckoutQuery -> Value
AnswerShippingQuery -> Encoding
AnswerShippingQuery -> Value
AnswerCallbackQuery -> Encoding
AnswerCallbackQuery -> Value
GetCallbackQueryAnswer -> Encoding
GetCallbackQueryAnswer -> Value
AnswerInlineQuery -> Encoding
AnswerInlineQuery -> Value
GetInlineQueryResults -> Encoding
GetInlineQueryResults -> Value
GetLoginUrl -> Encoding
GetLoginUrl -> Value
GetLoginUrlInfo -> Encoding
GetLoginUrlInfo -> Value
StopPoll -> Encoding
StopPoll -> Value
GetPollVoters -> Encoding
GetPollVoters -> Value
SetPollAnswer -> Encoding
SetPollAnswer -> Value
GetJsonString -> Encoding
GetJsonString -> Value
GetJsonValue -> Encoding
GetJsonValue -> Value
GetLanguagePackString -> Encoding
GetLanguagePackString -> Value
CleanFileName -> Encoding
CleanFileName -> Value
GetFileExtension -> Encoding
GetFileExtension -> Value
GetFileMimeType -> Encoding
GetFileMimeType -> Value
GetMarkdownText -> Encoding
GetMarkdownText -> Value
ParseMarkdown -> Encoding
ParseMarkdown -> Value
ParseTextEntities -> Encoding
ParseTextEntities -> Value
GetTextEntities -> Encoding
GetTextEntities -> Value
EditMessageSchedulingState -> Encoding
EditMessageSchedulingState -> Value
EditInlineMessageReplyMarkup -> Encoding
EditInlineMessageReplyMarkup -> Value
EditInlineMessageCaption -> Encoding
EditInlineMessageCaption -> Value
EditInlineMessageMedia -> Encoding
EditInlineMessageMedia -> Value
EditInlineMessageLiveLocation -> Encoding
EditInlineMessageLiveLocation -> Value
EditInlineMessageText -> Encoding
EditInlineMessageText -> Value
EditMessageReplyMarkup -> Encoding
EditMessageReplyMarkup -> Value
EditMessageCaption -> Encoding
EditMessageCaption -> Value
EditMessageMedia -> Encoding
EditMessageMedia -> Value
EditMessageLiveLocation -> Encoding
EditMessageLiveLocation -> Value
EditMessageText -> Encoding
EditMessageText -> Value
DeleteChatMessagesFromUser -> Encoding
DeleteChatMessagesFromUser -> Value
DeleteMessages -> Encoding
DeleteMessages -> Value
AddLocalMessage -> Encoding
AddLocalMessage -> Value
SendChatScreenshotTakenNotification -> Encoding
SendChatScreenshotTakenNotification -> Value
SendChatSetTtlMessage -> Encoding
SendChatSetTtlMessage -> Value
ResendMessages -> Encoding
ResendMessages -> Value
ForwardMessages -> Encoding
ForwardMessages -> Value
SendInlineQueryResultMessage -> Encoding
SendInlineQueryResultMessage -> Value
SendBotStartMessage -> Encoding
SendBotStartMessage -> Value
SendMessageAlbum -> Encoding
SendMessageAlbum -> Value
SendMessage -> Encoding
SendMessage -> Value
GetMessageLinkInfo -> Encoding
GetMessageLinkInfo -> Value
GetMessageLink -> Encoding
GetMessageLink -> Value
GetPublicMessageLink -> Encoding
GetPublicMessageLink -> Value
RemoveNotificationGroup -> Encoding
RemoveNotificationGroup -> Value
RemoveNotification -> Encoding
RemoveNotification -> Value
GetChatScheduledMessages -> Encoding
GetChatScheduledMessages -> Value
GetChatMessageCount -> Encoding
GetChatMessageCount -> Value
GetChatMessageByDate -> Encoding
GetChatMessageByDate -> Value
GetActiveLiveLocationMessages -> Encoding
GetActiveLiveLocationMessages -> Value
SearchChatRecentLocationMessages -> Encoding
SearchChatRecentLocationMessages -> Value
SearchCallMessages -> Encoding
SearchCallMessages -> Value
SearchSecretMessages -> Encoding
SearchSecretMessages -> Value
SearchMessages -> Encoding
SearchMessages -> Value
SearchChatMessages -> Encoding
SearchChatMessages -> Value
DeleteChatHistory -> Encoding
DeleteChatHistory -> Value
GetChatHistory -> Encoding
GetChatHistory -> Value
GetGroupsInCommon -> Encoding
GetGroupsInCommon -> Value
GetInactiveSupergroupChats -> Encoding
GetInactiveSupergroupChats -> Value
GetSuitableDiscussionChats -> Encoding
GetSuitableDiscussionChats -> Value
CheckCreatedPublicChatsLimit -> Encoding
CheckCreatedPublicChatsLimit -> Value
GetCreatedPublicChats -> Encoding
GetCreatedPublicChats -> Value
CheckChatUsername -> Encoding
CheckChatUsername -> Value
ClearRecentlyFoundChats -> Encoding
ClearRecentlyFoundChats -> Value
RemoveRecentlyFoundChat -> Encoding
RemoveRecentlyFoundChat -> Value
AddRecentlyFoundChat -> Encoding
AddRecentlyFoundChat -> Value
RemoveTopChat -> Encoding
RemoveTopChat -> Value
GetTopChats -> Encoding
GetTopChats -> Value
SearchChatsNearby -> Encoding
SearchChatsNearby -> Value
SearchChatsOnServer -> Encoding
SearchChatsOnServer -> Value
SearchChats -> Encoding
SearchChats -> Value
SearchPublicChats -> Encoding
SearchPublicChats -> Value
SearchPublicChat -> Encoding
SearchPublicChat -> Value
GetChats -> Encoding
GetChats -> Value
GetRemoteFile -> Encoding
GetRemoteFile -> Value
GetFile -> Encoding
GetFile -> Value
GetMessages -> Encoding
GetMessages -> Value
GetChatPinnedMessage -> Encoding
GetChatPinnedMessage -> Value
GetRepliedMessage -> Encoding
GetRepliedMessage -> Value
GetMessageLocally -> Encoding
GetMessageLocally -> Value
GetMessage -> Encoding
GetMessage -> Value
GetChat -> Encoding
GetChat -> Value
GetSecretChat -> Encoding
GetSecretChat -> Value
GetSupergroupFullInfo -> Encoding
GetSupergroupFullInfo -> Value
GetSupergroup -> Encoding
GetSupergroup -> Value
GetBasicGroupFullInfo -> Encoding
GetBasicGroupFullInfo -> Value
GetBasicGroup -> Encoding
GetBasicGroup -> Value
GetUserFullInfo -> Encoding
GetUserFullInfo -> Value
GetUser -> Encoding
GetUser -> Value
GetMe -> Encoding
GetMe -> Value
GetTemporaryPasswordState -> Encoding
GetTemporaryPasswordState -> Value
CreateTemporaryPassword -> Encoding
CreateTemporaryPassword -> Value
RecoverPassword -> Encoding
RecoverPassword -> Value
RequestPasswordRecovery -> Encoding
RequestPasswordRecovery -> Value
ResendRecoveryEmailAddressCode -> Encoding
ResendRecoveryEmailAddressCode -> Value
CheckRecoveryEmailAddressCode -> Encoding
CheckRecoveryEmailAddressCode -> Value
SetRecoveryEmailAddress -> Encoding
SetRecoveryEmailAddress -> Value
GetRecoveryEmailAddress -> Encoding
GetRecoveryEmailAddress -> Value
SetPassword -> Encoding
SetPassword -> Value
GetPasswordState -> Encoding
GetPasswordState -> Value
SetDatabaseEncryptionKey -> Encoding
SetDatabaseEncryptionKey -> Value
GetCurrentState -> Encoding
GetCurrentState -> Value
ConfirmQrCodeAuthentication -> Encoding
ConfirmQrCodeAuthentication -> Value
Destroy -> Encoding
Destroy -> Value
Close -> Encoding
Close -> Value
LogOut -> Encoding
LogOut -> Value
CheckAuthenticationBotToken -> Encoding
CheckAuthenticationBotToken -> Value
RecoverAuthenticationPassword -> Encoding
RecoverAuthenticationPassword -> Value
RequestAuthenticationPasswordRecovery -> Encoding
RequestAuthenticationPasswordRecovery -> Value
CheckAuthenticationPassword -> Encoding
CheckAuthenticationPassword -> Value
RegisterUser -> Encoding
RegisterUser -> Value
RequestQrCodeAuthentication -> Encoding
RequestQrCodeAuthentication -> Value
CheckAuthenticationCode -> Encoding
CheckAuthenticationCode -> Value
ResendAuthenticationCode -> Encoding
ResendAuthenticationCode -> Value
SetAuthenticationPhoneNumber -> Encoding
SetAuthenticationPhoneNumber -> Value
CheckDatabaseEncryptionKey -> Encoding
CheckDatabaseEncryptionKey -> Value
SetTdlibParameters -> Encoding
SetTdlibParameters -> Value
GetAuthorizationState -> Encoding
GetAuthorizationState -> Value
(Value -> Parser TestReturnError)
-> (Value -> Parser [TestReturnError]) -> FromJSON TestReturnError
(Value -> Parser TestUseUpdate)
-> (Value -> Parser [TestUseUpdate]) -> FromJSON TestUseUpdate
(Value -> Parser TestGetDifference)
-> (Value -> Parser [TestGetDifference])
-> FromJSON TestGetDifference
(Value -> Parser TestProxy)
-> (Value -> Parser [TestProxy]) -> FromJSON TestProxy
(Value -> Parser TestNetwork)
-> (Value -> Parser [TestNetwork]) -> FromJSON TestNetwork
(Value -> Parser TestSquareInt)
-> (Value -> Parser [TestSquareInt]) -> FromJSON TestSquareInt
(Value -> Parser TestCallVectorStringObject)
-> (Value -> Parser [TestCallVectorStringObject])
-> FromJSON TestCallVectorStringObject
(Value -> Parser TestCallVectorString)
-> (Value -> Parser [TestCallVectorString])
-> FromJSON TestCallVectorString
(Value -> Parser TestCallVectorIntObject)
-> (Value -> Parser [TestCallVectorIntObject])
-> FromJSON TestCallVectorIntObject
(Value -> Parser TestCallVectorInt)
-> (Value -> Parser [TestCallVectorInt])
-> FromJSON TestCallVectorInt
(Value -> Parser TestCallBytes)
-> (Value -> Parser [TestCallBytes]) -> FromJSON TestCallBytes
(Value -> Parser TestCallString)
-> (Value -> Parser [TestCallString]) -> FromJSON TestCallString
(Value -> Parser TestCallEmpty)
-> (Value -> Parser [TestCallEmpty]) -> FromJSON TestCallEmpty
(Value -> Parser AddLogMessage)
-> (Value -> Parser [AddLogMessage]) -> FromJSON AddLogMessage
(Value -> Parser GetLogTagVerbosityLevel)
-> (Value -> Parser [GetLogTagVerbosityLevel])
-> FromJSON GetLogTagVerbosityLevel
(Value -> Parser SetLogTagVerbosityLevel)
-> (Value -> Parser [SetLogTagVerbosityLevel])
-> FromJSON SetLogTagVerbosityLevel
(Value -> Parser GetLogTags)
-> (Value -> Parser [GetLogTags]) -> FromJSON GetLogTags
(Value -> Parser GetLogVerbosityLevel)
-> (Value -> Parser [GetLogVerbosityLevel])
-> FromJSON GetLogVerbosityLevel
(Value -> Parser SetLogVerbosityLevel)
-> (Value -> Parser [SetLogVerbosityLevel])
-> FromJSON SetLogVerbosityLevel
(Value -> Parser GetLogStream)
-> (Value -> Parser [GetLogStream]) -> FromJSON GetLogStream
(Value -> Parser SetLogStream)
-> (Value -> Parser [SetLogStream]) -> FromJSON SetLogStream
(Value -> Parser PingProxy)
-> (Value -> Parser [PingProxy]) -> FromJSON PingProxy
(Value -> Parser GetProxyLink)
-> (Value -> Parser [GetProxyLink]) -> FromJSON GetProxyLink
(Value -> Parser GetProxies)
-> (Value -> Parser [GetProxies]) -> FromJSON GetProxies
(Value -> Parser RemoveProxy)
-> (Value -> Parser [RemoveProxy]) -> FromJSON RemoveProxy
(Value -> Parser DisableProxy)
-> (Value -> Parser [DisableProxy]) -> FromJSON DisableProxy
(Value -> Parser EnableProxy)
-> (Value -> Parser [EnableProxy]) -> FromJSON EnableProxy
(Value -> Parser EditProxy)
-> (Value -> Parser [EditProxy]) -> FromJSON EditProxy
(Value -> Parser AddProxy)
-> (Value -> Parser [AddProxy]) -> FromJSON AddProxy
(Value -> Parser SaveApplicationLogEvent)
-> (Value -> Parser [SaveApplicationLogEvent])
-> FromJSON SaveApplicationLogEvent
(Value -> Parser GetApplicationConfig)
-> (Value -> Parser [GetApplicationConfig])
-> FromJSON GetApplicationConfig
(Value -> Parser GetDeepLinkInfo)
-> (Value -> Parser [GetDeepLinkInfo]) -> FromJSON GetDeepLinkInfo
(Value -> Parser GetInviteText)
-> (Value -> Parser [GetInviteText]) -> FromJSON GetInviteText
(Value -> Parser GetCountryCode)
-> (Value -> Parser [GetCountryCode]) -> FromJSON GetCountryCode
(Value -> Parser SetAlarm)
-> (Value -> Parser [SetAlarm]) -> FromJSON SetAlarm
(Value -> Parser AnswerCustomQuery)
-> (Value -> Parser [AnswerCustomQuery])
-> FromJSON AnswerCustomQuery
(Value -> Parser SendCustomRequest)
-> (Value -> Parser [SendCustomRequest])
-> FromJSON SendCustomRequest
(Value -> Parser AcceptTermsOfService)
-> (Value -> Parser [AcceptTermsOfService])
-> FromJSON AcceptTermsOfService
(Value -> Parser GetMapThumbnailFile)
-> (Value -> Parser [GetMapThumbnailFile])
-> FromJSON GetMapThumbnailFile
(Value -> Parser RemoveStickerFromSet)
-> (Value -> Parser [RemoveStickerFromSet])
-> FromJSON RemoveStickerFromSet
(Value -> Parser SetStickerPositionInSet)
-> (Value -> Parser [SetStickerPositionInSet])
-> FromJSON SetStickerPositionInSet
(Value -> Parser SetStickerSetThumbnail)
-> (Value -> Parser [SetStickerSetThumbnail])
-> FromJSON SetStickerSetThumbnail
(Value -> Parser AddStickerToSet)
-> (Value -> Parser [AddStickerToSet]) -> FromJSON AddStickerToSet
(Value -> Parser CreateNewStickerSet)
-> (Value -> Parser [CreateNewStickerSet])
-> FromJSON CreateNewStickerSet
(Value -> Parser UploadStickerFile)
-> (Value -> Parser [UploadStickerFile])
-> FromJSON UploadStickerFile
(Value -> Parser SetBotUpdatesStatus)
-> (Value -> Parser [SetBotUpdatesStatus])
-> FromJSON SetBotUpdatesStatus
(Value -> Parser CheckPhoneNumberConfirmationCode)
-> (Value -> Parser [CheckPhoneNumberConfirmationCode])
-> FromJSON CheckPhoneNumberConfirmationCode
(Value -> Parser ResendPhoneNumberConfirmationCode)
-> (Value -> Parser [ResendPhoneNumberConfirmationCode])
-> FromJSON ResendPhoneNumberConfirmationCode
(Value -> Parser SendPhoneNumberConfirmationCode)
-> (Value -> Parser [SendPhoneNumberConfirmationCode])
-> FromJSON SendPhoneNumberConfirmationCode
(Value -> Parser SendPassportAuthorizationForm)
-> (Value -> Parser [SendPassportAuthorizationForm])
-> FromJSON SendPassportAuthorizationForm
(Value -> Parser GetPassportAuthorizationFormAvailableElements)
-> (Value
    -> Parser [GetPassportAuthorizationFormAvailableElements])
-> FromJSON GetPassportAuthorizationFormAvailableElements
(Value -> Parser GetPassportAuthorizationForm)
-> (Value -> Parser [GetPassportAuthorizationForm])
-> FromJSON GetPassportAuthorizationForm
(Value -> Parser CheckEmailAddressVerificationCode)
-> (Value -> Parser [CheckEmailAddressVerificationCode])
-> FromJSON CheckEmailAddressVerificationCode
(Value -> Parser ResendEmailAddressVerificationCode)
-> (Value -> Parser [ResendEmailAddressVerificationCode])
-> FromJSON ResendEmailAddressVerificationCode
(Value -> Parser SendEmailAddressVerificationCode)
-> (Value -> Parser [SendEmailAddressVerificationCode])
-> FromJSON SendEmailAddressVerificationCode
(Value -> Parser CheckPhoneNumberVerificationCode)
-> (Value -> Parser [CheckPhoneNumberVerificationCode])
-> FromJSON CheckPhoneNumberVerificationCode
(Value -> Parser ResendPhoneNumberVerificationCode)
-> (Value -> Parser [ResendPhoneNumberVerificationCode])
-> FromJSON ResendPhoneNumberVerificationCode
(Value -> Parser SendPhoneNumberVerificationCode)
-> (Value -> Parser [SendPhoneNumberVerificationCode])
-> FromJSON SendPhoneNumberVerificationCode
(Value -> Parser GetPreferredCountryLanguage)
-> (Value -> Parser [GetPreferredCountryLanguage])
-> FromJSON GetPreferredCountryLanguage
(Value -> Parser SetPassportElementErrors)
-> (Value -> Parser [SetPassportElementErrors])
-> FromJSON SetPassportElementErrors
(Value -> Parser DeletePassportElement)
-> (Value -> Parser [DeletePassportElement])
-> FromJSON DeletePassportElement
(Value -> Parser SetPassportElement)
-> (Value -> Parser [SetPassportElement])
-> FromJSON SetPassportElement
(Value -> Parser GetAllPassportElements)
-> (Value -> Parser [GetAllPassportElements])
-> FromJSON GetAllPassportElements
(Value -> Parser GetPassportElement)
-> (Value -> Parser [GetPassportElement])
-> FromJSON GetPassportElement
(Value -> Parser GetBankCardInfo)
-> (Value -> Parser [GetBankCardInfo]) -> FromJSON GetBankCardInfo
(Value -> Parser SetAutoDownloadSettings)
-> (Value -> Parser [SetAutoDownloadSettings])
-> FromJSON SetAutoDownloadSettings
(Value -> Parser GetAutoDownloadSettingsPresets)
-> (Value -> Parser [GetAutoDownloadSettingsPresets])
-> FromJSON GetAutoDownloadSettingsPresets
(Value -> Parser ResetNetworkStatistics)
-> (Value -> Parser [ResetNetworkStatistics])
-> FromJSON ResetNetworkStatistics
(Value -> Parser AddNetworkStatistics)
-> (Value -> Parser [AddNetworkStatistics])
-> FromJSON AddNetworkStatistics
(Value -> Parser GetNetworkStatistics)
-> (Value -> Parser [GetNetworkStatistics])
-> FromJSON GetNetworkStatistics
(Value -> Parser SetNetworkType)
-> (Value -> Parser [SetNetworkType]) -> FromJSON SetNetworkType
(Value -> Parser OptimizeStorage)
-> (Value -> Parser [OptimizeStorage]) -> FromJSON OptimizeStorage
(Value -> Parser GetDatabaseStatistics)
-> (Value -> Parser [GetDatabaseStatistics])
-> FromJSON GetDatabaseStatistics
(Value -> Parser GetStorageStatisticsFast)
-> (Value -> Parser [GetStorageStatisticsFast])
-> FromJSON GetStorageStatisticsFast
(Value -> Parser GetStorageStatistics)
-> (Value -> Parser [GetStorageStatistics])
-> FromJSON GetStorageStatistics
(Value -> Parser GetChatStatisticsGraph)
-> (Value -> Parser [GetChatStatisticsGraph])
-> FromJSON GetChatStatisticsGraph
(Value -> Parser GetChatStatistics)
-> (Value -> Parser [GetChatStatistics])
-> FromJSON GetChatStatistics
(Value -> Parser GetChatStatisticsUrl)
-> (Value -> Parser [GetChatStatisticsUrl])
-> FromJSON GetChatStatisticsUrl
(Value -> Parser ReportChat)
-> (Value -> Parser [ReportChat]) -> FromJSON ReportChat
(Value -> Parser RemoveChatActionBar)
-> (Value -> Parser [RemoveChatActionBar])
-> FromJSON RemoveChatActionBar
(Value -> Parser DeleteAccount)
-> (Value -> Parser [DeleteAccount]) -> FromJSON DeleteAccount
(Value -> Parser GetAccountTtl)
-> (Value -> Parser [GetAccountTtl]) -> FromJSON GetAccountTtl
(Value -> Parser SetAccountTtl)
-> (Value -> Parser [SetAccountTtl]) -> FromJSON SetAccountTtl
(Value -> Parser SetOption)
-> (Value -> Parser [SetOption]) -> FromJSON SetOption
(Value -> Parser GetOption)
-> (Value -> Parser [GetOption]) -> FromJSON GetOption
(Value -> Parser GetUserPrivacySettingRules)
-> (Value -> Parser [GetUserPrivacySettingRules])
-> FromJSON GetUserPrivacySettingRules
(Value -> Parser SetUserPrivacySettingRules)
-> (Value -> Parser [SetUserPrivacySettingRules])
-> FromJSON SetUserPrivacySettingRules
(Value -> Parser GetRecentlyVisitedTMeUrls)
-> (Value -> Parser [GetRecentlyVisitedTMeUrls])
-> FromJSON GetRecentlyVisitedTMeUrls
(Value -> Parser GetPushReceiverId)
-> (Value -> Parser [GetPushReceiverId])
-> FromJSON GetPushReceiverId
(Value -> Parser ProcessPushNotification)
-> (Value -> Parser [ProcessPushNotification])
-> FromJSON ProcessPushNotification
(Value -> Parser RegisterDevice)
-> (Value -> Parser [RegisterDevice]) -> FromJSON RegisterDevice
(Value -> Parser DeleteLanguagePack)
-> (Value -> Parser [DeleteLanguagePack])
-> FromJSON DeleteLanguagePack
(Value -> Parser SetCustomLanguagePackString)
-> (Value -> Parser [SetCustomLanguagePackString])
-> FromJSON SetCustomLanguagePackString
(Value -> Parser EditCustomLanguagePackInfo)
-> (Value -> Parser [EditCustomLanguagePackInfo])
-> FromJSON EditCustomLanguagePackInfo
(Value -> Parser SetCustomLanguagePack)
-> (Value -> Parser [SetCustomLanguagePack])
-> FromJSON SetCustomLanguagePack
(Value -> Parser AddCustomServerLanguagePack)
-> (Value -> Parser [AddCustomServerLanguagePack])
-> FromJSON AddCustomServerLanguagePack
(Value -> Parser SynchronizeLanguagePack)
-> (Value -> Parser [SynchronizeLanguagePack])
-> FromJSON SynchronizeLanguagePack
(Value -> Parser GetLanguagePackStrings)
-> (Value -> Parser [GetLanguagePackStrings])
-> FromJSON GetLanguagePackStrings
(Value -> Parser GetLanguagePackInfo)
-> (Value -> Parser [GetLanguagePackInfo])
-> FromJSON GetLanguagePackInfo
(Value -> Parser GetLocalizationTargetInfo)
-> (Value -> Parser [GetLocalizationTargetInfo])
-> FromJSON GetLocalizationTargetInfo
(Value -> Parser ResetBackgrounds)
-> (Value -> Parser [ResetBackgrounds])
-> FromJSON ResetBackgrounds
(Value -> Parser RemoveBackground)
-> (Value -> Parser [RemoveBackground])
-> FromJSON RemoveBackground
(Value -> Parser SetBackground)
-> (Value -> Parser [SetBackground]) -> FromJSON SetBackground
(Value -> Parser SearchBackground)
-> (Value -> Parser [SearchBackground])
-> FromJSON SearchBackground
(Value -> Parser GetBackgroundUrl)
-> (Value -> Parser [GetBackgroundUrl])
-> FromJSON GetBackgroundUrl
(Value -> Parser GetBackgrounds)
-> (Value -> Parser [GetBackgrounds]) -> FromJSON GetBackgrounds
(Value -> Parser GetSupportUser)
-> (Value -> Parser [GetSupportUser]) -> FromJSON GetSupportUser
(Value -> Parser DeleteSavedCredentials)
-> (Value -> Parser [DeleteSavedCredentials])
-> FromJSON DeleteSavedCredentials
(Value -> Parser DeleteSavedOrderInfo)
-> (Value -> Parser [DeleteSavedOrderInfo])
-> FromJSON DeleteSavedOrderInfo
(Value -> Parser GetSavedOrderInfo)
-> (Value -> Parser [GetSavedOrderInfo])
-> FromJSON GetSavedOrderInfo
(Value -> Parser GetPaymentReceipt)
-> (Value -> Parser [GetPaymentReceipt])
-> FromJSON GetPaymentReceipt
(Value -> Parser SendPaymentForm)
-> (Value -> Parser [SendPaymentForm]) -> FromJSON SendPaymentForm
(Value -> Parser ValidateOrderInfo)
-> (Value -> Parser [ValidateOrderInfo])
-> FromJSON ValidateOrderInfo
(Value -> Parser GetPaymentForm)
-> (Value -> Parser [GetPaymentForm]) -> FromJSON GetPaymentForm
(Value -> Parser GetChatEventLog)
-> (Value -> Parser [GetChatEventLog]) -> FromJSON GetChatEventLog
(Value -> Parser CloseSecretChat)
-> (Value -> Parser [CloseSecretChat]) -> FromJSON CloseSecretChat
(Value -> Parser DeleteSupergroup)
-> (Value -> Parser [DeleteSupergroup])
-> FromJSON DeleteSupergroup
(Value -> Parser GetSupergroupMembers)
-> (Value -> Parser [GetSupergroupMembers])
-> FromJSON GetSupergroupMembers
(Value -> Parser ReportSupergroupSpam)
-> (Value -> Parser [ReportSupergroupSpam])
-> FromJSON ReportSupergroupSpam
(Value -> Parser ToggleSupergroupIsAllHistoryAvailable)
-> (Value -> Parser [ToggleSupergroupIsAllHistoryAvailable])
-> FromJSON ToggleSupergroupIsAllHistoryAvailable
(Value -> Parser ToggleSupergroupSignMessages)
-> (Value -> Parser [ToggleSupergroupSignMessages])
-> FromJSON ToggleSupergroupSignMessages
(Value -> Parser SetSupergroupStickerSet)
-> (Value -> Parser [SetSupergroupStickerSet])
-> FromJSON SetSupergroupStickerSet
(Value -> Parser SetSupergroupUsername)
-> (Value -> Parser [SetSupergroupUsername])
-> FromJSON SetSupergroupUsername
(Value -> Parser DisconnectAllWebsites)
-> (Value -> Parser [DisconnectAllWebsites])
-> FromJSON DisconnectAllWebsites
(Value -> Parser DisconnectWebsite)
-> (Value -> Parser [DisconnectWebsite])
-> FromJSON DisconnectWebsite
(Value -> Parser GetConnectedWebsites)
-> (Value -> Parser [GetConnectedWebsites])
-> FromJSON GetConnectedWebsites
(Value -> Parser TerminateAllOtherSessions)
-> (Value -> Parser [TerminateAllOtherSessions])
-> FromJSON TerminateAllOtherSessions
(Value -> Parser TerminateSession)
-> (Value -> Parser [TerminateSession])
-> FromJSON TerminateSession
(Value -> Parser GetActiveSessions)
-> (Value -> Parser [GetActiveSessions])
-> FromJSON GetActiveSessions
(Value -> Parser SetCommands)
-> (Value -> Parser [SetCommands]) -> FromJSON SetCommands
(Value -> Parser CheckChangePhoneNumberCode)
-> (Value -> Parser [CheckChangePhoneNumberCode])
-> FromJSON CheckChangePhoneNumberCode
(Value -> Parser ResendChangePhoneNumberCode)
-> (Value -> Parser [ResendChangePhoneNumberCode])
-> FromJSON ResendChangePhoneNumberCode
(Value -> Parser ChangePhoneNumber)
-> (Value -> Parser [ChangePhoneNumber])
-> FromJSON ChangePhoneNumber
(Value -> Parser SetLocation)
-> (Value -> Parser [SetLocation]) -> FromJSON SetLocation
(Value -> Parser SetUsername)
-> (Value -> Parser [SetUsername]) -> FromJSON SetUsername
(Value -> Parser SetBio)
-> (Value -> Parser [SetBio]) -> FromJSON SetBio
(Value -> Parser SetName)
-> (Value -> Parser [SetName]) -> FromJSON SetName
(Value -> Parser DeleteProfilePhoto)
-> (Value -> Parser [DeleteProfilePhoto])
-> FromJSON DeleteProfilePhoto
(Value -> Parser SetProfilePhoto)
-> (Value -> Parser [SetProfilePhoto]) -> FromJSON SetProfilePhoto
(Value -> Parser GetWebPageInstantView)
-> (Value -> Parser [GetWebPageInstantView])
-> FromJSON GetWebPageInstantView
(Value -> Parser GetWebPagePreview)
-> (Value -> Parser [GetWebPagePreview])
-> FromJSON GetWebPagePreview
(Value -> Parser RemoveRecentHashtag)
-> (Value -> Parser [RemoveRecentHashtag])
-> FromJSON RemoveRecentHashtag
(Value -> Parser SearchHashtags)
-> (Value -> Parser [SearchHashtags]) -> FromJSON SearchHashtags
(Value -> Parser GetRecentInlineBots)
-> (Value -> Parser [GetRecentInlineBots])
-> FromJSON GetRecentInlineBots
(Value -> Parser RemoveSavedAnimation)
-> (Value -> Parser [RemoveSavedAnimation])
-> FromJSON RemoveSavedAnimation
(Value -> Parser AddSavedAnimation)
-> (Value -> Parser [AddSavedAnimation])
-> FromJSON AddSavedAnimation
(Value -> Parser GetSavedAnimations)
-> (Value -> Parser [GetSavedAnimations])
-> FromJSON GetSavedAnimations
(Value -> Parser GetEmojiSuggestionsUrl)
-> (Value -> Parser [GetEmojiSuggestionsUrl])
-> FromJSON GetEmojiSuggestionsUrl
(Value -> Parser SearchEmojis)
-> (Value -> Parser [SearchEmojis]) -> FromJSON SearchEmojis
(Value -> Parser GetStickerEmojis)
-> (Value -> Parser [GetStickerEmojis])
-> FromJSON GetStickerEmojis
(Value -> Parser RemoveFavoriteSticker)
-> (Value -> Parser [RemoveFavoriteSticker])
-> FromJSON RemoveFavoriteSticker
(Value -> Parser AddFavoriteSticker)
-> (Value -> Parser [AddFavoriteSticker])
-> FromJSON AddFavoriteSticker
(Value -> Parser GetFavoriteStickers)
-> (Value -> Parser [GetFavoriteStickers])
-> FromJSON GetFavoriteStickers
(Value -> Parser ClearRecentStickers)
-> (Value -> Parser [ClearRecentStickers])
-> FromJSON ClearRecentStickers
(Value -> Parser RemoveRecentSticker)
-> (Value -> Parser [RemoveRecentSticker])
-> FromJSON RemoveRecentSticker
(Value -> Parser AddRecentSticker)
-> (Value -> Parser [AddRecentSticker])
-> FromJSON AddRecentSticker
(Value -> Parser GetRecentStickers)
-> (Value -> Parser [GetRecentStickers])
-> FromJSON GetRecentStickers
(Value -> Parser ReorderInstalledStickerSets)
-> (Value -> Parser [ReorderInstalledStickerSets])
-> FromJSON ReorderInstalledStickerSets
(Value -> Parser ViewTrendingStickerSets)
-> (Value -> Parser [ViewTrendingStickerSets])
-> FromJSON ViewTrendingStickerSets
(Value -> Parser ChangeStickerSet)
-> (Value -> Parser [ChangeStickerSet])
-> FromJSON ChangeStickerSet
(Value -> Parser SearchStickerSets)
-> (Value -> Parser [SearchStickerSets])
-> FromJSON SearchStickerSets
(Value -> Parser SearchInstalledStickerSets)
-> (Value -> Parser [SearchInstalledStickerSets])
-> FromJSON SearchInstalledStickerSets
(Value -> Parser SearchStickerSet)
-> (Value -> Parser [SearchStickerSet])
-> FromJSON SearchStickerSet
(Value -> Parser GetStickerSet)
-> (Value -> Parser [GetStickerSet]) -> FromJSON GetStickerSet
(Value -> Parser GetAttachedStickerSets)
-> (Value -> Parser [GetAttachedStickerSets])
-> FromJSON GetAttachedStickerSets
(Value -> Parser GetTrendingStickerSets)
-> (Value -> Parser [GetTrendingStickerSets])
-> FromJSON GetTrendingStickerSets
(Value -> Parser GetArchivedStickerSets)
-> (Value -> Parser [GetArchivedStickerSets])
-> FromJSON GetArchivedStickerSets
(Value -> Parser GetInstalledStickerSets)
-> (Value -> Parser [GetInstalledStickerSets])
-> FromJSON GetInstalledStickerSets
(Value -> Parser SearchStickers)
-> (Value -> Parser [SearchStickers]) -> FromJSON SearchStickers
(Value -> Parser GetStickers)
-> (Value -> Parser [GetStickers]) -> FromJSON GetStickers
(Value -> Parser GetUserProfilePhotos)
-> (Value -> Parser [GetUserProfilePhotos])
-> FromJSON GetUserProfilePhotos
(Value -> Parser SharePhoneNumber)
-> (Value -> Parser [SharePhoneNumber])
-> FromJSON SharePhoneNumber
(Value -> Parser ClearImportedContacts)
-> (Value -> Parser [ClearImportedContacts])
-> FromJSON ClearImportedContacts
(Value -> Parser ChangeImportedContacts)
-> (Value -> Parser [ChangeImportedContacts])
-> FromJSON ChangeImportedContacts
(Value -> Parser GetImportedContactCount)
-> (Value -> Parser [GetImportedContactCount])
-> FromJSON GetImportedContactCount
(Value -> Parser RemoveContacts)
-> (Value -> Parser [RemoveContacts]) -> FromJSON RemoveContacts
(Value -> Parser SearchContacts)
-> (Value -> Parser [SearchContacts]) -> FromJSON SearchContacts
(Value -> Parser GetContacts)
-> (Value -> Parser [GetContacts]) -> FromJSON GetContacts
(Value -> Parser ImportContacts)
-> (Value -> Parser [ImportContacts]) -> FromJSON ImportContacts
(Value -> Parser AddContact)
-> (Value -> Parser [AddContact]) -> FromJSON AddContact
(Value -> Parser GetBlockedUsers)
-> (Value -> Parser [GetBlockedUsers]) -> FromJSON GetBlockedUsers
(Value -> Parser UnblockUser)
-> (Value -> Parser [UnblockUser]) -> FromJSON UnblockUser
(Value -> Parser BlockUser)
-> (Value -> Parser [BlockUser]) -> FromJSON BlockUser
(Value -> Parser SendCallDebugInformation)
-> (Value -> Parser [SendCallDebugInformation])
-> FromJSON SendCallDebugInformation
(Value -> Parser SendCallRating)
-> (Value -> Parser [SendCallRating]) -> FromJSON SendCallRating
(Value -> Parser DiscardCall)
-> (Value -> Parser [DiscardCall]) -> FromJSON DiscardCall
(Value -> Parser AcceptCall)
-> (Value -> Parser [AcceptCall]) -> FromJSON AcceptCall
(Value -> Parser CreateCall)
-> (Value -> Parser [CreateCall]) -> FromJSON CreateCall
(Value -> Parser JoinChatByInviteLink)
-> (Value -> Parser [JoinChatByInviteLink])
-> FromJSON JoinChatByInviteLink
(Value -> Parser CheckChatInviteLink)
-> (Value -> Parser [CheckChatInviteLink])
-> FromJSON CheckChatInviteLink
(Value -> Parser GenerateChatInviteLink)
-> (Value -> Parser [GenerateChatInviteLink])
-> FromJSON GenerateChatInviteLink
(Value -> Parser DeleteFile)
-> (Value -> Parser [DeleteFile]) -> FromJSON DeleteFile
(Value -> Parser ReadFilePart)
-> (Value -> Parser [ReadFilePart]) -> FromJSON ReadFilePart
(Value -> Parser FinishFileGeneration)
-> (Value -> Parser [FinishFileGeneration])
-> FromJSON FinishFileGeneration
(Value -> Parser SetFileGenerationProgress)
-> (Value -> Parser [SetFileGenerationProgress])
-> FromJSON SetFileGenerationProgress
(Value -> Parser WriteGeneratedFilePart)
-> (Value -> Parser [WriteGeneratedFilePart])
-> FromJSON WriteGeneratedFilePart
(Value -> Parser CancelUploadFile)
-> (Value -> Parser [CancelUploadFile])
-> FromJSON CancelUploadFile
(Value -> Parser UploadFile)
-> (Value -> Parser [UploadFile]) -> FromJSON UploadFile
(Value -> Parser CancelDownloadFile)
-> (Value -> Parser [CancelDownloadFile])
-> FromJSON CancelDownloadFile
(Value -> Parser GetFileDownloadedPrefixSize)
-> (Value -> Parser [GetFileDownloadedPrefixSize])
-> FromJSON GetFileDownloadedPrefixSize
(Value -> Parser DownloadFile)
-> (Value -> Parser [DownloadFile]) -> FromJSON DownloadFile
(Value -> Parser SetPinnedChats)
-> (Value -> Parser [SetPinnedChats]) -> FromJSON SetPinnedChats
(Value -> Parser ResetAllNotificationSettings)
-> (Value -> Parser [ResetAllNotificationSettings])
-> FromJSON ResetAllNotificationSettings
(Value -> Parser SetScopeNotificationSettings)
-> (Value -> Parser [SetScopeNotificationSettings])
-> FromJSON SetScopeNotificationSettings
(Value -> Parser GetScopeNotificationSettings)
-> (Value -> Parser [GetScopeNotificationSettings])
-> FromJSON GetScopeNotificationSettings
(Value -> Parser GetChatNotificationSettingsExceptions)
-> (Value -> Parser [GetChatNotificationSettingsExceptions])
-> FromJSON GetChatNotificationSettingsExceptions
(Value -> Parser ClearAllDraftMessages)
-> (Value -> Parser [ClearAllDraftMessages])
-> FromJSON ClearAllDraftMessages
(Value -> Parser GetChatAdministrators)
-> (Value -> Parser [GetChatAdministrators])
-> FromJSON GetChatAdministrators
(Value -> Parser SearchChatMembers)
-> (Value -> Parser [SearchChatMembers])
-> FromJSON SearchChatMembers
(Value -> Parser GetChatMember)
-> (Value -> Parser [GetChatMember]) -> FromJSON GetChatMember
(Value -> Parser TransferChatOwnership)
-> (Value -> Parser [TransferChatOwnership])
-> FromJSON TransferChatOwnership
(Value -> Parser CanTransferOwnership)
-> (Value -> Parser [CanTransferOwnership])
-> FromJSON CanTransferOwnership
(Value -> Parser SetChatMemberStatus)
-> (Value -> Parser [SetChatMemberStatus])
-> FromJSON SetChatMemberStatus
(Value -> Parser AddChatMembers)
-> (Value -> Parser [AddChatMembers]) -> FromJSON AddChatMembers
(Value -> Parser AddChatMember)
-> (Value -> Parser [AddChatMember]) -> FromJSON AddChatMember
(Value -> Parser LeaveChat)
-> (Value -> Parser [LeaveChat]) -> FromJSON LeaveChat
(Value -> Parser JoinChat)
-> (Value -> Parser [JoinChat]) -> FromJSON JoinChat
(Value -> Parser UnpinChatMessage)
-> (Value -> Parser [UnpinChatMessage])
-> FromJSON UnpinChatMessage
(Value -> Parser PinChatMessage)
-> (Value -> Parser [PinChatMessage]) -> FromJSON PinChatMessage
(Value -> Parser SetChatSlowModeDelay)
-> (Value -> Parser [SetChatSlowModeDelay])
-> FromJSON SetChatSlowModeDelay
(Value -> Parser SetChatLocation)
-> (Value -> Parser [SetChatLocation]) -> FromJSON SetChatLocation
(Value -> Parser SetChatDiscussionGroup)
-> (Value -> Parser [SetChatDiscussionGroup])
-> FromJSON SetChatDiscussionGroup
(Value -> Parser SetChatDescription)
-> (Value -> Parser [SetChatDescription])
-> FromJSON SetChatDescription
(Value -> Parser SetChatClientData)
-> (Value -> Parser [SetChatClientData])
-> FromJSON SetChatClientData
(Value -> Parser ToggleChatDefaultDisableNotification)
-> (Value -> Parser [ToggleChatDefaultDisableNotification])
-> FromJSON ToggleChatDefaultDisableNotification
(Value -> Parser ToggleChatIsMarkedAsUnread)
-> (Value -> Parser [ToggleChatIsMarkedAsUnread])
-> FromJSON ToggleChatIsMarkedAsUnread
(Value -> Parser ToggleChatIsPinned)
-> (Value -> Parser [ToggleChatIsPinned])
-> FromJSON ToggleChatIsPinned
(Value -> Parser SetChatNotificationSettings)
-> (Value -> Parser [SetChatNotificationSettings])
-> FromJSON SetChatNotificationSettings
(Value -> Parser SetChatDraftMessage)
-> (Value -> Parser [SetChatDraftMessage])
-> FromJSON SetChatDraftMessage
(Value -> Parser SetChatPermissions)
-> (Value -> Parser [SetChatPermissions])
-> FromJSON SetChatPermissions
(Value -> Parser SetChatPhoto)
-> (Value -> Parser [SetChatPhoto]) -> FromJSON SetChatPhoto
(Value -> Parser SetChatTitle)
-> (Value -> Parser [SetChatTitle]) -> FromJSON SetChatTitle
(Value -> Parser SetChatChatList)
-> (Value -> Parser [SetChatChatList]) -> FromJSON SetChatChatList
(Value -> Parser UpgradeBasicGroupChatToSupergroupChat)
-> (Value -> Parser [UpgradeBasicGroupChatToSupergroupChat])
-> FromJSON UpgradeBasicGroupChatToSupergroupChat
(Value -> Parser CreateNewSecretChat)
-> (Value -> Parser [CreateNewSecretChat])
-> FromJSON CreateNewSecretChat
(Value -> Parser CreateNewSupergroupChat)
-> (Value -> Parser [CreateNewSupergroupChat])
-> FromJSON CreateNewSupergroupChat
(Value -> Parser CreateNewBasicGroupChat)
-> (Value -> Parser [CreateNewBasicGroupChat])
-> FromJSON CreateNewBasicGroupChat
(Value -> Parser CreateSecretChat)
-> (Value -> Parser [CreateSecretChat])
-> FromJSON CreateSecretChat
(Value -> Parser CreateSupergroupChat)
-> (Value -> Parser [CreateSupergroupChat])
-> FromJSON CreateSupergroupChat
(Value -> Parser CreateBasicGroupChat)
-> (Value -> Parser [CreateBasicGroupChat])
-> FromJSON CreateBasicGroupChat
(Value -> Parser CreatePrivateChat)
-> (Value -> Parser [CreatePrivateChat])
-> FromJSON CreatePrivateChat
(Value -> Parser ReadAllChatMentions)
-> (Value -> Parser [ReadAllChatMentions])
-> FromJSON ReadAllChatMentions
(Value -> Parser OpenMessageContent)
-> (Value -> Parser [OpenMessageContent])
-> FromJSON OpenMessageContent
(Value -> Parser ViewMessages)
-> (Value -> Parser [ViewMessages]) -> FromJSON ViewMessages
(Value -> Parser CloseChat)
-> (Value -> Parser [CloseChat]) -> FromJSON CloseChat
(Value -> Parser OpenChat)
-> (Value -> Parser [OpenChat]) -> FromJSON OpenChat
(Value -> Parser SendChatAction)
-> (Value -> Parser [SendChatAction]) -> FromJSON SendChatAction
(Value -> Parser DeleteChatReplyMarkup)
-> (Value -> Parser [DeleteChatReplyMarkup])
-> FromJSON DeleteChatReplyMarkup
(Value -> Parser GetInlineGameHighScores)
-> (Value -> Parser [GetInlineGameHighScores])
-> FromJSON GetInlineGameHighScores
(Value -> Parser GetGameHighScores)
-> (Value -> Parser [GetGameHighScores])
-> FromJSON GetGameHighScores
(Value -> Parser SetInlineGameScore)
-> (Value -> Parser [SetInlineGameScore])
-> FromJSON SetInlineGameScore
(Value -> Parser SetGameScore)
-> (Value -> Parser [SetGameScore]) -> FromJSON SetGameScore
(Value -> Parser AnswerPreCheckoutQuery)
-> (Value -> Parser [AnswerPreCheckoutQuery])
-> FromJSON AnswerPreCheckoutQuery
(Value -> Parser AnswerShippingQuery)
-> (Value -> Parser [AnswerShippingQuery])
-> FromJSON AnswerShippingQuery
(Value -> Parser AnswerCallbackQuery)
-> (Value -> Parser [AnswerCallbackQuery])
-> FromJSON AnswerCallbackQuery
(Value -> Parser GetCallbackQueryAnswer)
-> (Value -> Parser [GetCallbackQueryAnswer])
-> FromJSON GetCallbackQueryAnswer
(Value -> Parser AnswerInlineQuery)
-> (Value -> Parser [AnswerInlineQuery])
-> FromJSON AnswerInlineQuery
(Value -> Parser GetInlineQueryResults)
-> (Value -> Parser [GetInlineQueryResults])
-> FromJSON GetInlineQueryResults
(Value -> Parser GetLoginUrl)
-> (Value -> Parser [GetLoginUrl]) -> FromJSON GetLoginUrl
(Value -> Parser GetLoginUrlInfo)
-> (Value -> Parser [GetLoginUrlInfo]) -> FromJSON GetLoginUrlInfo
(Value -> Parser StopPoll)
-> (Value -> Parser [StopPoll]) -> FromJSON StopPoll
(Value -> Parser GetPollVoters)
-> (Value -> Parser [GetPollVoters]) -> FromJSON GetPollVoters
(Value -> Parser SetPollAnswer)
-> (Value -> Parser [SetPollAnswer]) -> FromJSON SetPollAnswer
(Value -> Parser GetJsonString)
-> (Value -> Parser [GetJsonString]) -> FromJSON GetJsonString
(Value -> Parser GetJsonValue)
-> (Value -> Parser [GetJsonValue]) -> FromJSON GetJsonValue
(Value -> Parser GetLanguagePackString)
-> (Value -> Parser [GetLanguagePackString])
-> FromJSON GetLanguagePackString
(Value -> Parser CleanFileName)
-> (Value -> Parser [CleanFileName]) -> FromJSON CleanFileName
(Value -> Parser GetFileExtension)
-> (Value -> Parser [GetFileExtension])
-> FromJSON GetFileExtension
(Value -> Parser GetFileMimeType)
-> (Value -> Parser [GetFileMimeType]) -> FromJSON GetFileMimeType
(Value -> Parser GetMarkdownText)
-> (Value -> Parser [GetMarkdownText]) -> FromJSON GetMarkdownText
(Value -> Parser ParseMarkdown)
-> (Value -> Parser [ParseMarkdown]) -> FromJSON ParseMarkdown
(Value -> Parser ParseTextEntities)
-> (Value -> Parser [ParseTextEntities])
-> FromJSON ParseTextEntities
(Value -> Parser GetTextEntities)
-> (Value -> Parser [GetTextEntities]) -> FromJSON GetTextEntities
(Value -> Parser EditMessageSchedulingState)
-> (Value -> Parser [EditMessageSchedulingState])
-> FromJSON EditMessageSchedulingState
(Value -> Parser EditInlineMessageReplyMarkup)
-> (Value -> Parser [EditInlineMessageReplyMarkup])
-> FromJSON EditInlineMessageReplyMarkup
(Value -> Parser EditInlineMessageCaption)
-> (Value -> Parser [EditInlineMessageCaption])
-> FromJSON EditInlineMessageCaption
(Value -> Parser EditInlineMessageMedia)
-> (Value -> Parser [EditInlineMessageMedia])
-> FromJSON EditInlineMessageMedia
(Value -> Parser EditInlineMessageLiveLocation)
-> (Value -> Parser [EditInlineMessageLiveLocation])
-> FromJSON EditInlineMessageLiveLocation
(Value -> Parser EditInlineMessageText)
-> (Value -> Parser [EditInlineMessageText])
-> FromJSON EditInlineMessageText
(Value -> Parser EditMessageReplyMarkup)
-> (Value -> Parser [EditMessageReplyMarkup])
-> FromJSON EditMessageReplyMarkup
(Value -> Parser EditMessageCaption)
-> (Value -> Parser [EditMessageCaption])
-> FromJSON EditMessageCaption
(Value -> Parser EditMessageMedia)
-> (Value -> Parser [EditMessageMedia])
-> FromJSON EditMessageMedia
(Value -> Parser EditMessageLiveLocation)
-> (Value -> Parser [EditMessageLiveLocation])
-> FromJSON EditMessageLiveLocation
(Value -> Parser EditMessageText)
-> (Value -> Parser [EditMessageText]) -> FromJSON EditMessageText
(Value -> Parser DeleteChatMessagesFromUser)
-> (Value -> Parser [DeleteChatMessagesFromUser])
-> FromJSON DeleteChatMessagesFromUser
(Value -> Parser DeleteMessages)
-> (Value -> Parser [DeleteMessages]) -> FromJSON DeleteMessages
(Value -> Parser AddLocalMessage)
-> (Value -> Parser [AddLocalMessage]) -> FromJSON AddLocalMessage
(Value -> Parser SendChatScreenshotTakenNotification)
-> (Value -> Parser [SendChatScreenshotTakenNotification])
-> FromJSON SendChatScreenshotTakenNotification
(Value -> Parser SendChatSetTtlMessage)
-> (Value -> Parser [SendChatSetTtlMessage])
-> FromJSON SendChatSetTtlMessage
(Value -> Parser ResendMessages)
-> (Value -> Parser [ResendMessages]) -> FromJSON ResendMessages
(Value -> Parser ForwardMessages)
-> (Value -> Parser [ForwardMessages]) -> FromJSON ForwardMessages
(Value -> Parser SendInlineQueryResultMessage)
-> (Value -> Parser [SendInlineQueryResultMessage])
-> FromJSON SendInlineQueryResultMessage
(Value -> Parser SendBotStartMessage)
-> (Value -> Parser [SendBotStartMessage])
-> FromJSON SendBotStartMessage
(Value -> Parser SendMessageAlbum)
-> (Value -> Parser [SendMessageAlbum])
-> FromJSON SendMessageAlbum
(Value -> Parser SendMessage)
-> (Value -> Parser [SendMessage]) -> FromJSON SendMessage
(Value -> Parser GetMessageLinkInfo)
-> (Value -> Parser [GetMessageLinkInfo])
-> FromJSON GetMessageLinkInfo
(Value -> Parser GetMessageLink)
-> (Value -> Parser [GetMessageLink]) -> FromJSON GetMessageLink
(Value -> Parser GetPublicMessageLink)
-> (Value -> Parser [GetPublicMessageLink])
-> FromJSON GetPublicMessageLink
(Value -> Parser RemoveNotificationGroup)
-> (Value -> Parser [RemoveNotificationGroup])
-> FromJSON RemoveNotificationGroup
(Value -> Parser RemoveNotification)
-> (Value -> Parser [RemoveNotification])
-> FromJSON RemoveNotification
(Value -> Parser GetChatScheduledMessages)
-> (Value -> Parser [GetChatScheduledMessages])
-> FromJSON GetChatScheduledMessages
(Value -> Parser GetChatMessageCount)
-> (Value -> Parser [GetChatMessageCount])
-> FromJSON GetChatMessageCount
(Value -> Parser GetChatMessageByDate)
-> (Value -> Parser [GetChatMessageByDate])
-> FromJSON GetChatMessageByDate
(Value -> Parser GetActiveLiveLocationMessages)
-> (Value -> Parser [GetActiveLiveLocationMessages])
-> FromJSON GetActiveLiveLocationMessages
(Value -> Parser SearchChatRecentLocationMessages)
-> (Value -> Parser [SearchChatRecentLocationMessages])
-> FromJSON SearchChatRecentLocationMessages
(Value -> Parser SearchCallMessages)
-> (Value -> Parser [SearchCallMessages])
-> FromJSON SearchCallMessages
(Value -> Parser SearchSecretMessages)
-> (Value -> Parser [SearchSecretMessages])
-> FromJSON SearchSecretMessages
(Value -> Parser SearchMessages)
-> (Value -> Parser [SearchMessages]) -> FromJSON SearchMessages
(Value -> Parser SearchChatMessages)
-> (Value -> Parser [SearchChatMessages])
-> FromJSON SearchChatMessages
(Value -> Parser DeleteChatHistory)
-> (Value -> Parser [DeleteChatHistory])
-> FromJSON DeleteChatHistory
(Value -> Parser GetChatHistory)
-> (Value -> Parser [GetChatHistory]) -> FromJSON GetChatHistory
(Value -> Parser GetGroupsInCommon)
-> (Value -> Parser [GetGroupsInCommon])
-> FromJSON GetGroupsInCommon
(Value -> Parser GetInactiveSupergroupChats)
-> (Value -> Parser [GetInactiveSupergroupChats])
-> FromJSON GetInactiveSupergroupChats
(Value -> Parser GetSuitableDiscussionChats)
-> (Value -> Parser [GetSuitableDiscussionChats])
-> FromJSON GetSuitableDiscussionChats
(Value -> Parser CheckCreatedPublicChatsLimit)
-> (Value -> Parser [CheckCreatedPublicChatsLimit])
-> FromJSON CheckCreatedPublicChatsLimit
(Value -> Parser GetCreatedPublicChats)
-> (Value -> Parser [GetCreatedPublicChats])
-> FromJSON GetCreatedPublicChats
(Value -> Parser CheckChatUsername)
-> (Value -> Parser [CheckChatUsername])
-> FromJSON CheckChatUsername
(Value -> Parser ClearRecentlyFoundChats)
-> (Value -> Parser [ClearRecentlyFoundChats])
-> FromJSON ClearRecentlyFoundChats
(Value -> Parser RemoveRecentlyFoundChat)
-> (Value -> Parser [RemoveRecentlyFoundChat])
-> FromJSON RemoveRecentlyFoundChat
(Value -> Parser AddRecentlyFoundChat)
-> (Value -> Parser [AddRecentlyFoundChat])
-> FromJSON AddRecentlyFoundChat
(Value -> Parser RemoveTopChat)
-> (Value -> Parser [RemoveTopChat]) -> FromJSON RemoveTopChat
(Value -> Parser GetTopChats)
-> (Value -> Parser [GetTopChats]) -> FromJSON GetTopChats
(Value -> Parser SearchChatsNearby)
-> (Value -> Parser [SearchChatsNearby])
-> FromJSON SearchChatsNearby
(Value -> Parser SearchChatsOnServer)
-> (Value -> Parser [SearchChatsOnServer])
-> FromJSON SearchChatsOnServer
(Value -> Parser SearchChats)
-> (Value -> Parser [SearchChats]) -> FromJSON SearchChats
(Value -> Parser SearchPublicChats)
-> (Value -> Parser [SearchPublicChats])
-> FromJSON SearchPublicChats
(Value -> Parser SearchPublicChat)
-> (Value -> Parser [SearchPublicChat])
-> FromJSON SearchPublicChat
(Value -> Parser GetChats)
-> (Value -> Parser [GetChats]) -> FromJSON GetChats
(Value -> Parser GetRemoteFile)
-> (Value -> Parser [GetRemoteFile]) -> FromJSON GetRemoteFile
(Value -> Parser GetFile)
-> (Value -> Parser [GetFile]) -> FromJSON GetFile
(Value -> Parser GetMessages)
-> (Value -> Parser [GetMessages]) -> FromJSON GetMessages
(Value -> Parser GetChatPinnedMessage)
-> (Value -> Parser [GetChatPinnedMessage])
-> FromJSON GetChatPinnedMessage
(Value -> Parser GetRepliedMessage)
-> (Value -> Parser [GetRepliedMessage])
-> FromJSON GetRepliedMessage
(Value -> Parser GetMessageLocally)
-> (Value -> Parser [GetMessageLocally])
-> FromJSON GetMessageLocally
(Value -> Parser GetMessage)
-> (Value -> Parser [GetMessage]) -> FromJSON GetMessage
(Value -> Parser GetChat)
-> (Value -> Parser [GetChat]) -> FromJSON GetChat
(Value -> Parser GetSecretChat)
-> (Value -> Parser [GetSecretChat]) -> FromJSON GetSecretChat
(Value -> Parser GetSupergroupFullInfo)
-> (Value -> Parser [GetSupergroupFullInfo])
-> FromJSON GetSupergroupFullInfo
(Value -> Parser GetSupergroup)
-> (Value -> Parser [GetSupergroup]) -> FromJSON GetSupergroup
(Value -> Parser GetBasicGroupFullInfo)
-> (Value -> Parser [GetBasicGroupFullInfo])
-> FromJSON GetBasicGroupFullInfo
(Value -> Parser GetBasicGroup)
-> (Value -> Parser [GetBasicGroup]) -> FromJSON GetBasicGroup
(Value -> Parser GetUserFullInfo)
-> (Value -> Parser [GetUserFullInfo]) -> FromJSON GetUserFullInfo
(Value -> Parser GetUser)
-> (Value -> Parser [GetUser]) -> FromJSON GetUser
(Value -> Parser GetMe)
-> (Value -> Parser [GetMe]) -> FromJSON GetMe
(Value -> Parser GetTemporaryPasswordState)
-> (Value -> Parser [GetTemporaryPasswordState])
-> FromJSON GetTemporaryPasswordState
(Value -> Parser CreateTemporaryPassword)
-> (Value -> Parser [CreateTemporaryPassword])
-> FromJSON CreateTemporaryPassword
(Value -> Parser RecoverPassword)
-> (Value -> Parser [RecoverPassword]) -> FromJSON RecoverPassword
(Value -> Parser RequestPasswordRecovery)
-> (Value -> Parser [RequestPasswordRecovery])
-> FromJSON RequestPasswordRecovery
(Value -> Parser ResendRecoveryEmailAddressCode)
-> (Value -> Parser [ResendRecoveryEmailAddressCode])
-> FromJSON ResendRecoveryEmailAddressCode
(Value -> Parser CheckRecoveryEmailAddressCode)
-> (Value -> Parser [CheckRecoveryEmailAddressCode])
-> FromJSON CheckRecoveryEmailAddressCode
(Value -> Parser SetRecoveryEmailAddress)
-> (Value -> Parser [SetRecoveryEmailAddress])
-> FromJSON SetRecoveryEmailAddress
(Value -> Parser GetRecoveryEmailAddress)
-> (Value -> Parser [GetRecoveryEmailAddress])
-> FromJSON GetRecoveryEmailAddress
(Value -> Parser SetPassword)
-> (Value -> Parser [SetPassword]) -> FromJSON SetPassword
(Value -> Parser GetPasswordState)
-> (Value -> Parser [GetPasswordState])
-> FromJSON GetPasswordState
(Value -> Parser SetDatabaseEncryptionKey)
-> (Value -> Parser [SetDatabaseEncryptionKey])
-> FromJSON SetDatabaseEncryptionKey
(Value -> Parser GetCurrentState)
-> (Value -> Parser [GetCurrentState]) -> FromJSON GetCurrentState
(Value -> Parser ConfirmQrCodeAuthentication)
-> (Value -> Parser [ConfirmQrCodeAuthentication])
-> FromJSON ConfirmQrCodeAuthentication
(Value -> Parser Destroy)
-> (Value -> Parser [Destroy]) -> FromJSON Destroy
(Value -> Parser Close)
-> (Value -> Parser [Close]) -> FromJSON Close
(Value -> Parser LogOut)
-> (Value -> Parser [LogOut]) -> FromJSON LogOut
(Value -> Parser CheckAuthenticationBotToken)
-> (Value -> Parser [CheckAuthenticationBotToken])
-> FromJSON CheckAuthenticationBotToken
(Value -> Parser RecoverAuthenticationPassword)
-> (Value -> Parser [RecoverAuthenticationPassword])
-> FromJSON RecoverAuthenticationPassword
(Value -> Parser RequestAuthenticationPasswordRecovery)
-> (Value -> Parser [RequestAuthenticationPasswordRecovery])
-> FromJSON RequestAuthenticationPasswordRecovery
(Value -> Parser CheckAuthenticationPassword)
-> (Value -> Parser [CheckAuthenticationPassword])
-> FromJSON CheckAuthenticationPassword
(Value -> Parser RegisterUser)
-> (Value -> Parser [RegisterUser]) -> FromJSON RegisterUser
(Value -> Parser RequestQrCodeAuthentication)
-> (Value -> Parser [RequestQrCodeAuthentication])
-> FromJSON RequestQrCodeAuthentication
(Value -> Parser CheckAuthenticationCode)
-> (Value -> Parser [CheckAuthenticationCode])
-> FromJSON CheckAuthenticationCode
(Value -> Parser ResendAuthenticationCode)
-> (Value -> Parser [ResendAuthenticationCode])
-> FromJSON ResendAuthenticationCode
(Value -> Parser SetAuthenticationPhoneNumber)
-> (Value -> Parser [SetAuthenticationPhoneNumber])
-> FromJSON SetAuthenticationPhoneNumber
(Value -> Parser CheckDatabaseEncryptionKey)
-> (Value -> Parser [CheckDatabaseEncryptionKey])
-> FromJSON CheckDatabaseEncryptionKey
(Value -> Parser SetTdlibParameters)
-> (Value -> Parser [SetTdlibParameters])
-> FromJSON SetTdlibParameters
(Value -> Parser GetAuthorizationState)
-> (Value -> Parser [GetAuthorizationState])
-> FromJSON GetAuthorizationState
(TestReturnError -> Value)
-> (TestReturnError -> Encoding)
-> ([TestReturnError] -> Value)
-> ([TestReturnError] -> Encoding)
-> ToJSON TestReturnError
(TestUseUpdate -> Value)
-> (TestUseUpdate -> Encoding)
-> ([TestUseUpdate] -> Value)
-> ([TestUseUpdate] -> Encoding)
-> ToJSON TestUseUpdate
(TestGetDifference -> Value)
-> (TestGetDifference -> Encoding)
-> ([TestGetDifference] -> Value)
-> ([TestGetDifference] -> Encoding)
-> ToJSON TestGetDifference
(TestProxy -> Value)
-> (TestProxy -> Encoding)
-> ([TestProxy] -> Value)
-> ([TestProxy] -> Encoding)
-> ToJSON TestProxy
(TestNetwork -> Value)
-> (TestNetwork -> Encoding)
-> ([TestNetwork] -> Value)
-> ([TestNetwork] -> Encoding)
-> ToJSON TestNetwork
(TestSquareInt -> Value)
-> (TestSquareInt -> Encoding)
-> ([TestSquareInt] -> Value)
-> ([TestSquareInt] -> Encoding)
-> ToJSON TestSquareInt
(TestCallVectorStringObject -> Value)
-> (TestCallVectorStringObject -> Encoding)
-> ([TestCallVectorStringObject] -> Value)
-> ([TestCallVectorStringObject] -> Encoding)
-> ToJSON TestCallVectorStringObject
(TestCallVectorString -> Value)
-> (TestCallVectorString -> Encoding)
-> ([TestCallVectorString] -> Value)
-> ([TestCallVectorString] -> Encoding)
-> ToJSON TestCallVectorString
(TestCallVectorIntObject -> Value)
-> (TestCallVectorIntObject -> Encoding)
-> ([TestCallVectorIntObject] -> Value)
-> ([TestCallVectorIntObject] -> Encoding)
-> ToJSON TestCallVectorIntObject
(TestCallVectorInt -> Value)
-> (TestCallVectorInt -> Encoding)
-> ([TestCallVectorInt] -> Value)
-> ([TestCallVectorInt] -> Encoding)
-> ToJSON TestCallVectorInt
(TestCallBytes -> Value)
-> (TestCallBytes -> Encoding)
-> ([TestCallBytes] -> Value)
-> ([TestCallBytes] -> Encoding)
-> ToJSON TestCallBytes
(TestCallString -> Value)
-> (TestCallString -> Encoding)
-> ([TestCallString] -> Value)
-> ([TestCallString] -> Encoding)
-> ToJSON TestCallString
(TestCallEmpty -> Value)
-> (TestCallEmpty -> Encoding)
-> ([TestCallEmpty] -> Value)
-> ([TestCallEmpty] -> Encoding)
-> ToJSON TestCallEmpty
(AddLogMessage -> Value)
-> (AddLogMessage -> Encoding)
-> ([AddLogMessage] -> Value)
-> ([AddLogMessage] -> Encoding)
-> ToJSON AddLogMessage
(GetLogTagVerbosityLevel -> Value)
-> (GetLogTagVerbosityLevel -> Encoding)
-> ([GetLogTagVerbosityLevel] -> Value)
-> ([GetLogTagVerbosityLevel] -> Encoding)
-> ToJSON GetLogTagVerbosityLevel
(SetLogTagVerbosityLevel -> Value)
-> (SetLogTagVerbosityLevel -> Encoding)
-> ([SetLogTagVerbosityLevel] -> Value)
-> ([SetLogTagVerbosityLevel] -> Encoding)
-> ToJSON SetLogTagVerbosityLevel
(GetLogTags -> Value)
-> (GetLogTags -> Encoding)
-> ([GetLogTags] -> Value)
-> ([GetLogTags] -> Encoding)
-> ToJSON GetLogTags
(GetLogVerbosityLevel -> Value)
-> (GetLogVerbosityLevel -> Encoding)
-> ([GetLogVerbosityLevel] -> Value)
-> ([GetLogVerbosityLevel] -> Encoding)
-> ToJSON GetLogVerbosityLevel
(SetLogVerbosityLevel -> Value)
-> (SetLogVerbosityLevel -> Encoding)
-> ([SetLogVerbosityLevel] -> Value)
-> ([SetLogVerbosityLevel] -> Encoding)
-> ToJSON SetLogVerbosityLevel
(GetLogStream -> Value)
-> (GetLogStream -> Encoding)
-> ([GetLogStream] -> Value)
-> ([GetLogStream] -> Encoding)
-> ToJSON GetLogStream
(SetLogStream -> Value)
-> (SetLogStream -> Encoding)
-> ([SetLogStream] -> Value)
-> ([SetLogStream] -> Encoding)
-> ToJSON SetLogStream
(PingProxy -> Value)
-> (PingProxy -> Encoding)
-> ([PingProxy] -> Value)
-> ([PingProxy] -> Encoding)
-> ToJSON PingProxy
(GetProxyLink -> Value)
-> (GetProxyLink -> Encoding)
-> ([GetProxyLink] -> Value)
-> ([GetProxyLink] -> Encoding)
-> ToJSON GetProxyLink
(GetProxies -> Value)
-> (GetProxies -> Encoding)
-> ([GetProxies] -> Value)
-> ([GetProxies] -> Encoding)
-> ToJSON GetProxies
(RemoveProxy -> Value)
-> (RemoveProxy -> Encoding)
-> ([RemoveProxy] -> Value)
-> ([RemoveProxy] -> Encoding)
-> ToJSON RemoveProxy
(DisableProxy -> Value)
-> (DisableProxy -> Encoding)
-> ([DisableProxy] -> Value)
-> ([DisableProxy] -> Encoding)
-> ToJSON DisableProxy
(EnableProxy -> Value)
-> (EnableProxy -> Encoding)
-> ([EnableProxy] -> Value)
-> ([EnableProxy] -> Encoding)
-> ToJSON EnableProxy
(EditProxy -> Value)
-> (EditProxy -> Encoding)
-> ([EditProxy] -> Value)
-> ([EditProxy] -> Encoding)
-> ToJSON EditProxy
(AddProxy -> Value)
-> (AddProxy -> Encoding)
-> ([AddProxy] -> Value)
-> ([AddProxy] -> Encoding)
-> ToJSON AddProxy
(SaveApplicationLogEvent -> Value)
-> (SaveApplicationLogEvent -> Encoding)
-> ([SaveApplicationLogEvent] -> Value)
-> ([SaveApplicationLogEvent] -> Encoding)
-> ToJSON SaveApplicationLogEvent
(GetApplicationConfig -> Value)
-> (GetApplicationConfig -> Encoding)
-> ([GetApplicationConfig] -> Value)
-> ([GetApplicationConfig] -> Encoding)
-> ToJSON GetApplicationConfig
(GetDeepLinkInfo -> Value)
-> (GetDeepLinkInfo -> Encoding)
-> ([GetDeepLinkInfo] -> Value)
-> ([GetDeepLinkInfo] -> Encoding)
-> ToJSON GetDeepLinkInfo
(GetInviteText -> Value)
-> (GetInviteText -> Encoding)
-> ([GetInviteText] -> Value)
-> ([GetInviteText] -> Encoding)
-> ToJSON GetInviteText
(GetCountryCode -> Value)
-> (GetCountryCode -> Encoding)
-> ([GetCountryCode] -> Value)
-> ([GetCountryCode] -> Encoding)
-> ToJSON GetCountryCode
(SetAlarm -> Value)
-> (SetAlarm -> Encoding)
-> ([SetAlarm] -> Value)
-> ([SetAlarm] -> Encoding)
-> ToJSON SetAlarm
(AnswerCustomQuery -> Value)
-> (AnswerCustomQuery -> Encoding)
-> ([AnswerCustomQuery] -> Value)
-> ([AnswerCustomQuery] -> Encoding)
-> ToJSON AnswerCustomQuery
(SendCustomRequest -> Value)
-> (SendCustomRequest -> Encoding)
-> ([SendCustomRequest] -> Value)
-> ([SendCustomRequest] -> Encoding)
-> ToJSON SendCustomRequest
(AcceptTermsOfService -> Value)
-> (AcceptTermsOfService -> Encoding)
-> ([AcceptTermsOfService] -> Value)
-> ([AcceptTermsOfService] -> Encoding)
-> ToJSON AcceptTermsOfService
(GetMapThumbnailFile -> Value)
-> (GetMapThumbnailFile -> Encoding)
-> ([GetMapThumbnailFile] -> Value)
-> ([GetMapThumbnailFile] -> Encoding)
-> ToJSON GetMapThumbnailFile
(RemoveStickerFromSet -> Value)
-> (RemoveStickerFromSet -> Encoding)
-> ([RemoveStickerFromSet] -> Value)
-> ([RemoveStickerFromSet] -> Encoding)
-> ToJSON RemoveStickerFromSet
(SetStickerPositionInSet -> Value)
-> (SetStickerPositionInSet -> Encoding)
-> ([SetStickerPositionInSet] -> Value)
-> ([SetStickerPositionInSet] -> Encoding)
-> ToJSON SetStickerPositionInSet
(SetStickerSetThumbnail -> Value)
-> (SetStickerSetThumbnail -> Encoding)
-> ([SetStickerSetThumbnail] -> Value)
-> ([SetStickerSetThumbnail] -> Encoding)
-> ToJSON SetStickerSetThumbnail
(AddStickerToSet -> Value)
-> (AddStickerToSet -> Encoding)
-> ([AddStickerToSet] -> Value)
-> ([AddStickerToSet] -> Encoding)
-> ToJSON AddStickerToSet
(CreateNewStickerSet -> Value)
-> (CreateNewStickerSet -> Encoding)
-> ([CreateNewStickerSet] -> Value)
-> ([CreateNewStickerSet] -> Encoding)
-> ToJSON CreateNewStickerSet
(UploadStickerFile -> Value)
-> (UploadStickerFile -> Encoding)
-> ([UploadStickerFile] -> Value)
-> ([UploadStickerFile] -> Encoding)
-> ToJSON UploadStickerFile
(SetBotUpdatesStatus -> Value)
-> (SetBotUpdatesStatus -> Encoding)
-> ([SetBotUpdatesStatus] -> Value)
-> ([SetBotUpdatesStatus] -> Encoding)
-> ToJSON SetBotUpdatesStatus
(CheckPhoneNumberConfirmationCode -> Value)
-> (CheckPhoneNumberConfirmationCode -> Encoding)
-> ([CheckPhoneNumberConfirmationCode] -> Value)
-> ([CheckPhoneNumberConfirmationCode] -> Encoding)
-> ToJSON CheckPhoneNumberConfirmationCode
(ResendPhoneNumberConfirmationCode -> Value)
-> (ResendPhoneNumberConfirmationCode -> Encoding)
-> ([ResendPhoneNumberConfirmationCode] -> Value)
-> ([ResendPhoneNumberConfirmationCode] -> Encoding)
-> ToJSON ResendPhoneNumberConfirmationCode
(SendPhoneNumberConfirmationCode -> Value)
-> (SendPhoneNumberConfirmationCode -> Encoding)
-> ([SendPhoneNumberConfirmationCode] -> Value)
-> ([SendPhoneNumberConfirmationCode] -> Encoding)
-> ToJSON SendPhoneNumberConfirmationCode
(SendPassportAuthorizationForm -> Value)
-> (SendPassportAuthorizationForm -> Encoding)
-> ([SendPassportAuthorizationForm] -> Value)
-> ([SendPassportAuthorizationForm] -> Encoding)
-> ToJSON SendPassportAuthorizationForm
(GetPassportAuthorizationFormAvailableElements -> Value)
-> (GetPassportAuthorizationFormAvailableElements -> Encoding)
-> ([GetPassportAuthorizationFormAvailableElements] -> Value)
-> ([GetPassportAuthorizationFormAvailableElements] -> Encoding)
-> ToJSON GetPassportAuthorizationFormAvailableElements
(GetPassportAuthorizationForm -> Value)
-> (GetPassportAuthorizationForm -> Encoding)
-> ([GetPassportAuthorizationForm] -> Value)
-> ([GetPassportAuthorizationForm] -> Encoding)
-> ToJSON GetPassportAuthorizationForm
(CheckEmailAddressVerificationCode -> Value)
-> (CheckEmailAddressVerificationCode -> Encoding)
-> ([CheckEmailAddressVerificationCode] -> Value)
-> ([CheckEmailAddressVerificationCode] -> Encoding)
-> ToJSON CheckEmailAddressVerificationCode
(ResendEmailAddressVerificationCode -> Value)
-> (ResendEmailAddressVerificationCode -> Encoding)
-> ([ResendEmailAddressVerificationCode] -> Value)
-> ([ResendEmailAddressVerificationCode] -> Encoding)
-> ToJSON ResendEmailAddressVerificationCode
(SendEmailAddressVerificationCode -> Value)
-> (SendEmailAddressVerificationCode -> Encoding)
-> ([SendEmailAddressVerificationCode] -> Value)
-> ([SendEmailAddressVerificationCode] -> Encoding)
-> ToJSON SendEmailAddressVerificationCode
(CheckPhoneNumberVerificationCode -> Value)
-> (CheckPhoneNumberVerificationCode -> Encoding)
-> ([CheckPhoneNumberVerificationCode] -> Value)
-> ([CheckPhoneNumberVerificationCode] -> Encoding)
-> ToJSON CheckPhoneNumberVerificationCode
(ResendPhoneNumberVerificationCode -> Value)
-> (ResendPhoneNumberVerificationCode -> Encoding)
-> ([ResendPhoneNumberVerificationCode] -> Value)
-> ([ResendPhoneNumberVerificationCode] -> Encoding)
-> ToJSON ResendPhoneNumberVerificationCode
(SendPhoneNumberVerificationCode -> Value)
-> (SendPhoneNumberVerificationCode -> Encoding)
-> ([SendPhoneNumberVerificationCode] -> Value)
-> ([SendPhoneNumberVerificationCode] -> Encoding)
-> ToJSON SendPhoneNumberVerificationCode
(GetPreferredCountryLanguage -> Value)
-> (GetPreferredCountryLanguage -> Encoding)
-> ([GetPreferredCountryLanguage] -> Value)
-> ([GetPreferredCountryLanguage] -> Encoding)
-> ToJSON GetPreferredCountryLanguage
(SetPassportElementErrors -> Value)
-> (SetPassportElementErrors -> Encoding)
-> ([SetPassportElementErrors] -> Value)
-> ([SetPassportElementErrors] -> Encoding)
-> ToJSON SetPassportElementErrors
(DeletePassportElement -> Value)
-> (DeletePassportElement -> Encoding)
-> ([DeletePassportElement] -> Value)
-> ([DeletePassportElement] -> Encoding)
-> ToJSON DeletePassportElement
(SetPassportElement -> Value)
-> (SetPassportElement -> Encoding)
-> ([SetPassportElement] -> Value)
-> ([SetPassportElement] -> Encoding)
-> ToJSON SetPassportElement
(GetAllPassportElements -> Value)
-> (GetAllPassportElements -> Encoding)
-> ([GetAllPassportElements] -> Value)
-> ([GetAllPassportElements] -> Encoding)
-> ToJSON GetAllPassportElements
(GetPassportElement -> Value)
-> (GetPassportElement -> Encoding)
-> ([GetPassportElement] -> Value)
-> ([GetPassportElement] -> Encoding)
-> ToJSON GetPassportElement
(GetBankCardInfo -> Value)
-> (GetBankCardInfo -> Encoding)
-> ([GetBankCardInfo] -> Value)
-> ([GetBankCardInfo] -> Encoding)
-> ToJSON GetBankCardInfo
(SetAutoDownloadSettings -> Value)
-> (SetAutoDownloadSettings -> Encoding)
-> ([SetAutoDownloadSettings] -> Value)
-> ([SetAutoDownloadSettings] -> Encoding)
-> ToJSON SetAutoDownloadSettings
(GetAutoDownloadSettingsPresets -> Value)
-> (GetAutoDownloadSettingsPresets -> Encoding)
-> ([GetAutoDownloadSettingsPresets] -> Value)
-> ([GetAutoDownloadSettingsPresets] -> Encoding)
-> ToJSON GetAutoDownloadSettingsPresets
(ResetNetworkStatistics -> Value)
-> (ResetNetworkStatistics -> Encoding)
-> ([ResetNetworkStatistics] -> Value)
-> ([ResetNetworkStatistics] -> Encoding)
-> ToJSON ResetNetworkStatistics
(AddNetworkStatistics -> Value)
-> (AddNetworkStatistics -> Encoding)
-> ([AddNetworkStatistics] -> Value)
-> ([AddNetworkStatistics] -> Encoding)
-> ToJSON AddNetworkStatistics
(GetNetworkStatistics -> Value)
-> (GetNetworkStatistics -> Encoding)
-> ([GetNetworkStatistics] -> Value)
-> ([GetNetworkStatistics] -> Encoding)
-> ToJSON GetNetworkStatistics
(SetNetworkType -> Value)
-> (SetNetworkType -> Encoding)
-> ([SetNetworkType] -> Value)
-> ([SetNetworkType] -> Encoding)
-> ToJSON SetNetworkType
(OptimizeStorage -> Value)
-> (OptimizeStorage -> Encoding)
-> ([OptimizeStorage] -> Value)
-> ([OptimizeStorage] -> Encoding)
-> ToJSON OptimizeStorage
(GetDatabaseStatistics -> Value)
-> (GetDatabaseStatistics -> Encoding)
-> ([GetDatabaseStatistics] -> Value)
-> ([GetDatabaseStatistics] -> Encoding)
-> ToJSON GetDatabaseStatistics
(GetStorageStatisticsFast -> Value)
-> (GetStorageStatisticsFast -> Encoding)
-> ([GetStorageStatisticsFast] -> Value)
-> ([GetStorageStatisticsFast] -> Encoding)
-> ToJSON GetStorageStatisticsFast
(GetStorageStatistics -> Value)
-> (GetStorageStatistics -> Encoding)
-> ([GetStorageStatistics] -> Value)
-> ([GetStorageStatistics] -> Encoding)
-> ToJSON GetStorageStatistics
(GetChatStatisticsGraph -> Value)
-> (GetChatStatisticsGraph -> Encoding)
-> ([GetChatStatisticsGraph] -> Value)
-> ([GetChatStatisticsGraph] -> Encoding)
-> ToJSON GetChatStatisticsGraph
(GetChatStatistics -> Value)
-> (GetChatStatistics -> Encoding)
-> ([GetChatStatistics] -> Value)
-> ([GetChatStatistics] -> Encoding)
-> ToJSON GetChatStatistics
(GetChatStatisticsUrl -> Value)
-> (GetChatStatisticsUrl -> Encoding)
-> ([GetChatStatisticsUrl] -> Value)
-> ([GetChatStatisticsUrl] -> Encoding)
-> ToJSON GetChatStatisticsUrl
(ReportChat -> Value)
-> (ReportChat -> Encoding)
-> ([ReportChat] -> Value)
-> ([ReportChat] -> Encoding)
-> ToJSON ReportChat
(RemoveChatActionBar -> Value)
-> (RemoveChatActionBar -> Encoding)
-> ([RemoveChatActionBar] -> Value)
-> ([RemoveChatActionBar] -> Encoding)
-> ToJSON RemoveChatActionBar
(DeleteAccount -> Value)
-> (DeleteAccount -> Encoding)
-> ([DeleteAccount] -> Value)
-> ([DeleteAccount] -> Encoding)
-> ToJSON DeleteAccount
(GetAccountTtl -> Value)
-> (GetAccountTtl -> Encoding)
-> ([GetAccountTtl] -> Value)
-> ([GetAccountTtl] -> Encoding)
-> ToJSON GetAccountTtl
(SetAccountTtl -> Value)
-> (SetAccountTtl -> Encoding)
-> ([SetAccountTtl] -> Value)
-> ([SetAccountTtl] -> Encoding)
-> ToJSON SetAccountTtl
(SetOption -> Value)
-> (SetOption -> Encoding)
-> ([SetOption] -> Value)
-> ([SetOption] -> Encoding)
-> ToJSON SetOption
(GetOption -> Value)
-> (GetOption -> Encoding)
-> ([GetOption] -> Value)
-> ([GetOption] -> Encoding)
-> ToJSON GetOption
(GetUserPrivacySettingRules -> Value)
-> (GetUserPrivacySettingRules -> Encoding)
-> ([GetUserPrivacySettingRules] -> Value)
-> ([GetUserPrivacySettingRules] -> Encoding)
-> ToJSON GetUserPrivacySettingRules
(SetUserPrivacySettingRules -> Value)
-> (SetUserPrivacySettingRules -> Encoding)
-> ([SetUserPrivacySettingRules] -> Value)
-> ([SetUserPrivacySettingRules] -> Encoding)
-> ToJSON SetUserPrivacySettingRules
(GetRecentlyVisitedTMeUrls -> Value)
-> (GetRecentlyVisitedTMeUrls -> Encoding)
-> ([GetRecentlyVisitedTMeUrls] -> Value)
-> ([GetRecentlyVisitedTMeUrls] -> Encoding)
-> ToJSON GetRecentlyVisitedTMeUrls
(GetPushReceiverId -> Value)
-> (GetPushReceiverId -> Encoding)
-> ([GetPushReceiverId] -> Value)
-> ([GetPushReceiverId] -> Encoding)
-> ToJSON GetPushReceiverId
(ProcessPushNotification -> Value)
-> (ProcessPushNotification -> Encoding)
-> ([ProcessPushNotification] -> Value)
-> ([ProcessPushNotification] -> Encoding)
-> ToJSON ProcessPushNotification
(RegisterDevice -> Value)
-> (RegisterDevice -> Encoding)
-> ([RegisterDevice] -> Value)
-> ([RegisterDevice] -> Encoding)
-> ToJSON RegisterDevice
(DeleteLanguagePack -> Value)
-> (DeleteLanguagePack -> Encoding)
-> ([DeleteLanguagePack] -> Value)
-> ([DeleteLanguagePack] -> Encoding)
-> ToJSON DeleteLanguagePack
(SetCustomLanguagePackString -> Value)
-> (SetCustomLanguagePackString -> Encoding)
-> ([SetCustomLanguagePackString] -> Value)
-> ([SetCustomLanguagePackString] -> Encoding)
-> ToJSON SetCustomLanguagePackString
(EditCustomLanguagePackInfo -> Value)
-> (EditCustomLanguagePackInfo -> Encoding)
-> ([EditCustomLanguagePackInfo] -> Value)
-> ([EditCustomLanguagePackInfo] -> Encoding)
-> ToJSON EditCustomLanguagePackInfo
(SetCustomLanguagePack -> Value)
-> (SetCustomLanguagePack -> Encoding)
-> ([SetCustomLanguagePack] -> Value)
-> ([SetCustomLanguagePack] -> Encoding)
-> ToJSON SetCustomLanguagePack
(AddCustomServerLanguagePack -> Value)
-> (AddCustomServerLanguagePack -> Encoding)
-> ([AddCustomServerLanguagePack] -> Value)
-> ([AddCustomServerLanguagePack] -> Encoding)
-> ToJSON AddCustomServerLanguagePack
(SynchronizeLanguagePack -> Value)
-> (SynchronizeLanguagePack -> Encoding)
-> ([SynchronizeLanguagePack] -> Value)
-> ([SynchronizeLanguagePack] -> Encoding)
-> ToJSON SynchronizeLanguagePack
(GetLanguagePackStrings -> Value)
-> (GetLanguagePackStrings -> Encoding)
-> ([GetLanguagePackStrings] -> Value)
-> ([GetLanguagePackStrings] -> Encoding)
-> ToJSON GetLanguagePackStrings
(GetLanguagePackInfo -> Value)
-> (GetLanguagePackInfo -> Encoding)
-> ([GetLanguagePackInfo] -> Value)
-> ([GetLanguagePackInfo] -> Encoding)
-> ToJSON GetLanguagePackInfo
(GetLocalizationTargetInfo -> Value)
-> (GetLocalizationTargetInfo -> Encoding)
-> ([GetLocalizationTargetInfo] -> Value)
-> ([GetLocalizationTargetInfo] -> Encoding)
-> ToJSON GetLocalizationTargetInfo
(ResetBackgrounds -> Value)
-> (ResetBackgrounds -> Encoding)
-> ([ResetBackgrounds] -> Value)
-> ([ResetBackgrounds] -> Encoding)
-> ToJSON ResetBackgrounds
(RemoveBackground -> Value)
-> (RemoveBackground -> Encoding)
-> ([RemoveBackground] -> Value)
-> ([RemoveBackground] -> Encoding)
-> ToJSON RemoveBackground
(SetBackground -> Value)
-> (SetBackground -> Encoding)
-> ([SetBackground] -> Value)
-> ([SetBackground] -> Encoding)
-> ToJSON SetBackground
(SearchBackground -> Value)
-> (SearchBackground -> Encoding)
-> ([SearchBackground] -> Value)
-> ([SearchBackground] -> Encoding)
-> ToJSON SearchBackground
(GetBackgroundUrl -> Value)
-> (GetBackgroundUrl -> Encoding)
-> ([GetBackgroundUrl] -> Value)
-> ([GetBackgroundUrl] -> Encoding)
-> ToJSON GetBackgroundUrl
(GetBackgrounds -> Value)
-> (GetBackgrounds -> Encoding)
-> ([GetBackgrounds] -> Value)
-> ([GetBackgrounds] -> Encoding)
-> ToJSON GetBackgrounds
(GetSupportUser -> Value)
-> (GetSupportUser -> Encoding)
-> ([GetSupportUser] -> Value)
-> ([GetSupportUser] -> Encoding)
-> ToJSON GetSupportUser
(DeleteSavedCredentials -> Value)
-> (DeleteSavedCredentials -> Encoding)
-> ([DeleteSavedCredentials] -> Value)
-> ([DeleteSavedCredentials] -> Encoding)
-> ToJSON DeleteSavedCredentials
(DeleteSavedOrderInfo -> Value)
-> (DeleteSavedOrderInfo -> Encoding)
-> ([DeleteSavedOrderInfo] -> Value)
-> ([DeleteSavedOrderInfo] -> Encoding)
-> ToJSON DeleteSavedOrderInfo
(GetSavedOrderInfo -> Value)
-> (GetSavedOrderInfo -> Encoding)
-> ([GetSavedOrderInfo] -> Value)
-> ([GetSavedOrderInfo] -> Encoding)
-> ToJSON GetSavedOrderInfo
(GetPaymentReceipt -> Value)
-> (GetPaymentReceipt -> Encoding)
-> ([GetPaymentReceipt] -> Value)
-> ([GetPaymentReceipt] -> Encoding)
-> ToJSON GetPaymentReceipt
(SendPaymentForm -> Value)
-> (SendPaymentForm -> Encoding)
-> ([SendPaymentForm] -> Value)
-> ([SendPaymentForm] -> Encoding)
-> ToJSON SendPaymentForm
(ValidateOrderInfo -> Value)
-> (ValidateOrderInfo -> Encoding)
-> ([ValidateOrderInfo] -> Value)
-> ([ValidateOrderInfo] -> Encoding)
-> ToJSON ValidateOrderInfo
(GetPaymentForm -> Value)
-> (GetPaymentForm -> Encoding)
-> ([GetPaymentForm] -> Value)
-> ([GetPaymentForm] -> Encoding)
-> ToJSON GetPaymentForm
(GetChatEventLog -> Value)
-> (GetChatEventLog -> Encoding)
-> ([GetChatEventLog] -> Value)
-> ([GetChatEventLog] -> Encoding)
-> ToJSON GetChatEventLog
(CloseSecretChat -> Value)
-> (CloseSecretChat -> Encoding)
-> ([CloseSecretChat] -> Value)
-> ([CloseSecretChat] -> Encoding)
-> ToJSON CloseSecretChat
(DeleteSupergroup -> Value)
-> (DeleteSupergroup -> Encoding)
-> ([DeleteSupergroup] -> Value)
-> ([DeleteSupergroup] -> Encoding)
-> ToJSON DeleteSupergroup
(GetSupergroupMembers -> Value)
-> (GetSupergroupMembers -> Encoding)
-> ([GetSupergroupMembers] -> Value)
-> ([GetSupergroupMembers] -> Encoding)
-> ToJSON GetSupergroupMembers
(ReportSupergroupSpam -> Value)
-> (ReportSupergroupSpam -> Encoding)
-> ([ReportSupergroupSpam] -> Value)
-> ([ReportSupergroupSpam] -> Encoding)
-> ToJSON ReportSupergroupSpam
(ToggleSupergroupIsAllHistoryAvailable -> Value)
-> (ToggleSupergroupIsAllHistoryAvailable -> Encoding)
-> ([ToggleSupergroupIsAllHistoryAvailable] -> Value)
-> ([ToggleSupergroupIsAllHistoryAvailable] -> Encoding)
-> ToJSON ToggleSupergroupIsAllHistoryAvailable
(ToggleSupergroupSignMessages -> Value)
-> (ToggleSupergroupSignMessages -> Encoding)
-> ([ToggleSupergroupSignMessages] -> Value)
-> ([ToggleSupergroupSignMessages] -> Encoding)
-> ToJSON ToggleSupergroupSignMessages
(SetSupergroupStickerSet -> Value)
-> (SetSupergroupStickerSet -> Encoding)
-> ([SetSupergroupStickerSet] -> Value)
-> ([SetSupergroupStickerSet] -> Encoding)
-> ToJSON SetSupergroupStickerSet
(SetSupergroupUsername -> Value)
-> (SetSupergroupUsername -> Encoding)
-> ([SetSupergroupUsername] -> Value)
-> ([SetSupergroupUsername] -> Encoding)
-> ToJSON SetSupergroupUsername
(DisconnectAllWebsites -> Value)
-> (DisconnectAllWebsites -> Encoding)
-> ([DisconnectAllWebsites] -> Value)
-> ([DisconnectAllWebsites] -> Encoding)
-> ToJSON DisconnectAllWebsites
(DisconnectWebsite -> Value)
-> (DisconnectWebsite -> Encoding)
-> ([DisconnectWebsite] -> Value)
-> ([DisconnectWebsite] -> Encoding)
-> ToJSON DisconnectWebsite
(GetConnectedWebsites -> Value)
-> (GetConnectedWebsites -> Encoding)
-> ([GetConnectedWebsites] -> Value)
-> ([GetConnectedWebsites] -> Encoding)
-> ToJSON GetConnectedWebsites
(TerminateAllOtherSessions -> Value)
-> (TerminateAllOtherSessions -> Encoding)
-> ([TerminateAllOtherSessions] -> Value)
-> ([TerminateAllOtherSessions] -> Encoding)
-> ToJSON TerminateAllOtherSessions
(TerminateSession -> Value)
-> (TerminateSession -> Encoding)
-> ([TerminateSession] -> Value)
-> ([TerminateSession] -> Encoding)
-> ToJSON TerminateSession
(GetActiveSessions -> Value)
-> (GetActiveSessions -> Encoding)
-> ([GetActiveSessions] -> Value)
-> ([GetActiveSessions] -> Encoding)
-> ToJSON GetActiveSessions
(SetCommands -> Value)
-> (SetCommands -> Encoding)
-> ([SetCommands] -> Value)
-> ([SetCommands] -> Encoding)
-> ToJSON SetCommands
(CheckChangePhoneNumberCode -> Value)
-> (CheckChangePhoneNumberCode -> Encoding)
-> ([CheckChangePhoneNumberCode] -> Value)
-> ([CheckChangePhoneNumberCode] -> Encoding)
-> ToJSON CheckChangePhoneNumberCode
(ResendChangePhoneNumberCode -> Value)
-> (ResendChangePhoneNumberCode -> Encoding)
-> ([ResendChangePhoneNumberCode] -> Value)
-> ([ResendChangePhoneNumberCode] -> Encoding)
-> ToJSON ResendChangePhoneNumberCode
(ChangePhoneNumber -> Value)
-> (ChangePhoneNumber -> Encoding)
-> ([ChangePhoneNumber] -> Value)
-> ([ChangePhoneNumber] -> Encoding)
-> ToJSON ChangePhoneNumber
(SetLocation -> Value)
-> (SetLocation -> Encoding)
-> ([SetLocation] -> Value)
-> ([SetLocation] -> Encoding)
-> ToJSON SetLocation
(SetUsername -> Value)
-> (SetUsername -> Encoding)
-> ([SetUsername] -> Value)
-> ([SetUsername] -> Encoding)
-> ToJSON SetUsername
(SetBio -> Value)
-> (SetBio -> Encoding)
-> ([SetBio] -> Value)
-> ([SetBio] -> Encoding)
-> ToJSON SetBio
(SetName -> Value)
-> (SetName -> Encoding)
-> ([SetName] -> Value)
-> ([SetName] -> Encoding)
-> ToJSON SetName
(DeleteProfilePhoto -> Value)
-> (DeleteProfilePhoto -> Encoding)
-> ([DeleteProfilePhoto] -> Value)
-> ([DeleteProfilePhoto] -> Encoding)
-> ToJSON DeleteProfilePhoto
(SetProfilePhoto -> Value)
-> (SetProfilePhoto -> Encoding)
-> ([SetProfilePhoto] -> Value)
-> ([SetProfilePhoto] -> Encoding)
-> ToJSON SetProfilePhoto
(GetWebPageInstantView -> Value)
-> (GetWebPageInstantView -> Encoding)
-> ([GetWebPageInstantView] -> Value)
-> ([GetWebPageInstantView] -> Encoding)
-> ToJSON GetWebPageInstantView
(GetWebPagePreview -> Value)
-> (GetWebPagePreview -> Encoding)
-> ([GetWebPagePreview] -> Value)
-> ([GetWebPagePreview] -> Encoding)
-> ToJSON GetWebPagePreview
(RemoveRecentHashtag -> Value)
-> (RemoveRecentHashtag -> Encoding)
-> ([RemoveRecentHashtag] -> Value)
-> ([RemoveRecentHashtag] -> Encoding)
-> ToJSON RemoveRecentHashtag
(SearchHashtags -> Value)
-> (SearchHashtags -> Encoding)
-> ([SearchHashtags] -> Value)
-> ([SearchHashtags] -> Encoding)
-> ToJSON SearchHashtags
(GetRecentInlineBots -> Value)
-> (GetRecentInlineBots -> Encoding)
-> ([GetRecentInlineBots] -> Value)
-> ([GetRecentInlineBots] -> Encoding)
-> ToJSON GetRecentInlineBots
(RemoveSavedAnimation -> Value)
-> (RemoveSavedAnimation -> Encoding)
-> ([RemoveSavedAnimation] -> Value)
-> ([RemoveSavedAnimation] -> Encoding)
-> ToJSON RemoveSavedAnimation
(AddSavedAnimation -> Value)
-> (AddSavedAnimation -> Encoding)
-> ([AddSavedAnimation] -> Value)
-> ([AddSavedAnimation] -> Encoding)
-> ToJSON AddSavedAnimation
(GetSavedAnimations -> Value)
-> (GetSavedAnimations -> Encoding)
-> ([GetSavedAnimations] -> Value)
-> ([GetSavedAnimations] -> Encoding)
-> ToJSON GetSavedAnimations
(GetEmojiSuggestionsUrl -> Value)
-> (GetEmojiSuggestionsUrl -> Encoding)
-> ([GetEmojiSuggestionsUrl] -> Value)
-> ([GetEmojiSuggestionsUrl] -> Encoding)
-> ToJSON GetEmojiSuggestionsUrl
(SearchEmojis -> Value)
-> (SearchEmojis -> Encoding)
-> ([SearchEmojis] -> Value)
-> ([SearchEmojis] -> Encoding)
-> ToJSON SearchEmojis
(GetStickerEmojis -> Value)
-> (GetStickerEmojis -> Encoding)
-> ([GetStickerEmojis] -> Value)
-> ([GetStickerEmojis] -> Encoding)
-> ToJSON GetStickerEmojis
(RemoveFavoriteSticker -> Value)
-> (RemoveFavoriteSticker -> Encoding)
-> ([RemoveFavoriteSticker] -> Value)
-> ([RemoveFavoriteSticker] -> Encoding)
-> ToJSON RemoveFavoriteSticker
(AddFavoriteSticker -> Value)
-> (AddFavoriteSticker -> Encoding)
-> ([AddFavoriteSticker] -> Value)
-> ([AddFavoriteSticker] -> Encoding)
-> ToJSON AddFavoriteSticker
(GetFavoriteStickers -> Value)
-> (GetFavoriteStickers -> Encoding)
-> ([GetFavoriteStickers] -> Value)
-> ([GetFavoriteStickers] -> Encoding)
-> ToJSON GetFavoriteStickers
(ClearRecentStickers -> Value)
-> (ClearRecentStickers -> Encoding)
-> ([ClearRecentStickers] -> Value)
-> ([ClearRecentStickers] -> Encoding)
-> ToJSON ClearRecentStickers
(RemoveRecentSticker -> Value)
-> (RemoveRecentSticker -> Encoding)
-> ([RemoveRecentSticker] -> Value)
-> ([RemoveRecentSticker] -> Encoding)
-> ToJSON RemoveRecentSticker
(AddRecentSticker -> Value)
-> (AddRecentSticker -> Encoding)
-> ([AddRecentSticker] -> Value)
-> ([AddRecentSticker] -> Encoding)
-> ToJSON AddRecentSticker
(GetRecentStickers -> Value)
-> (GetRecentStickers -> Encoding)
-> ([GetRecentStickers] -> Value)
-> ([GetRecentStickers] -> Encoding)
-> ToJSON GetRecentStickers
(ReorderInstalledStickerSets -> Value)
-> (ReorderInstalledStickerSets -> Encoding)
-> ([ReorderInstalledStickerSets] -> Value)
-> ([ReorderInstalledStickerSets] -> Encoding)
-> ToJSON ReorderInstalledStickerSets
(ViewTrendingStickerSets -> Value)
-> (ViewTrendingStickerSets -> Encoding)
-> ([ViewTrendingStickerSets] -> Value)
-> ([ViewTrendingStickerSets] -> Encoding)
-> ToJSON ViewTrendingStickerSets
(ChangeStickerSet -> Value)
-> (ChangeStickerSet -> Encoding)
-> ([ChangeStickerSet] -> Value)
-> ([ChangeStickerSet] -> Encoding)
-> ToJSON ChangeStickerSet
(SearchStickerSets -> Value)
-> (SearchStickerSets -> Encoding)
-> ([SearchStickerSets] -> Value)
-> ([SearchStickerSets] -> Encoding)
-> ToJSON SearchStickerSets
(SearchInstalledStickerSets -> Value)
-> (SearchInstalledStickerSets -> Encoding)
-> ([SearchInstalledStickerSets] -> Value)
-> ([SearchInstalledStickerSets] -> Encoding)
-> ToJSON SearchInstalledStickerSets
(SearchStickerSet -> Value)
-> (SearchStickerSet -> Encoding)
-> ([SearchStickerSet] -> Value)
-> ([SearchStickerSet] -> Encoding)
-> ToJSON SearchStickerSet
(GetStickerSet -> Value)
-> (GetStickerSet -> Encoding)
-> ([GetStickerSet] -> Value)
-> ([GetStickerSet] -> Encoding)
-> ToJSON GetStickerSet
(GetAttachedStickerSets -> Value)
-> (GetAttachedStickerSets -> Encoding)
-> ([GetAttachedStickerSets] -> Value)
-> ([GetAttachedStickerSets] -> Encoding)
-> ToJSON GetAttachedStickerSets
(GetTrendingStickerSets -> Value)
-> (GetTrendingStickerSets -> Encoding)
-> ([GetTrendingStickerSets] -> Value)
-> ([GetTrendingStickerSets] -> Encoding)
-> ToJSON GetTrendingStickerSets
(GetArchivedStickerSets -> Value)
-> (GetArchivedStickerSets -> Encoding)
-> ([GetArchivedStickerSets] -> Value)
-> ([GetArchivedStickerSets] -> Encoding)
-> ToJSON GetArchivedStickerSets
(GetInstalledStickerSets -> Value)
-> (GetInstalledStickerSets -> Encoding)
-> ([GetInstalledStickerSets] -> Value)
-> ([GetInstalledStickerSets] -> Encoding)
-> ToJSON GetInstalledStickerSets
(SearchStickers -> Value)
-> (SearchStickers -> Encoding)
-> ([SearchStickers] -> Value)
-> ([SearchStickers] -> Encoding)
-> ToJSON SearchStickers
(GetStickers -> Value)
-> (GetStickers -> Encoding)
-> ([GetStickers] -> Value)
-> ([GetStickers] -> Encoding)
-> ToJSON GetStickers
(GetUserProfilePhotos -> Value)
-> (GetUserProfilePhotos -> Encoding)
-> ([GetUserProfilePhotos] -> Value)
-> ([GetUserProfilePhotos] -> Encoding)
-> ToJSON GetUserProfilePhotos
(SharePhoneNumber -> Value)
-> (SharePhoneNumber -> Encoding)
-> ([SharePhoneNumber] -> Value)
-> ([SharePhoneNumber] -> Encoding)
-> ToJSON SharePhoneNumber
(ClearImportedContacts -> Value)
-> (ClearImportedContacts -> Encoding)
-> ([ClearImportedContacts] -> Value)
-> ([ClearImportedContacts] -> Encoding)
-> ToJSON ClearImportedContacts
(ChangeImportedContacts -> Value)
-> (ChangeImportedContacts -> Encoding)
-> ([ChangeImportedContacts] -> Value)
-> ([ChangeImportedContacts] -> Encoding)
-> ToJSON ChangeImportedContacts
(GetImportedContactCount -> Value)
-> (GetImportedContactCount -> Encoding)
-> ([GetImportedContactCount] -> Value)
-> ([GetImportedContactCount] -> Encoding)
-> ToJSON GetImportedContactCount
(RemoveContacts -> Value)
-> (RemoveContacts -> Encoding)
-> ([RemoveContacts] -> Value)
-> ([RemoveContacts] -> Encoding)
-> ToJSON RemoveContacts
(SearchContacts -> Value)
-> (SearchContacts -> Encoding)
-> ([SearchContacts] -> Value)
-> ([SearchContacts] -> Encoding)
-> ToJSON SearchContacts
(GetContacts -> Value)
-> (GetContacts -> Encoding)
-> ([GetContacts] -> Value)
-> ([GetContacts] -> Encoding)
-> ToJSON GetContacts
(ImportContacts -> Value)
-> (ImportContacts -> Encoding)
-> ([ImportContacts] -> Value)
-> ([ImportContacts] -> Encoding)
-> ToJSON ImportContacts
(AddContact -> Value)
-> (AddContact -> Encoding)
-> ([AddContact] -> Value)
-> ([AddContact] -> Encoding)
-> ToJSON AddContact
(GetBlockedUsers -> Value)
-> (GetBlockedUsers -> Encoding)
-> ([GetBlockedUsers] -> Value)
-> ([GetBlockedUsers] -> Encoding)
-> ToJSON GetBlockedUsers
(UnblockUser -> Value)
-> (UnblockUser -> Encoding)
-> ([UnblockUser] -> Value)
-> ([UnblockUser] -> Encoding)
-> ToJSON UnblockUser
(BlockUser -> Value)
-> (BlockUser -> Encoding)
-> ([BlockUser] -> Value)
-> ([BlockUser] -> Encoding)
-> ToJSON BlockUser
(SendCallDebugInformation -> Value)
-> (SendCallDebugInformation -> Encoding)
-> ([SendCallDebugInformation] -> Value)
-> ([SendCallDebugInformation] -> Encoding)
-> ToJSON SendCallDebugInformation
(SendCallRating -> Value)
-> (SendCallRating -> Encoding)
-> ([SendCallRating] -> Value)
-> ([SendCallRating] -> Encoding)
-> ToJSON SendCallRating
(DiscardCall -> Value)
-> (DiscardCall -> Encoding)
-> ([DiscardCall] -> Value)
-> ([DiscardCall] -> Encoding)
-> ToJSON DiscardCall
(AcceptCall -> Value)
-> (AcceptCall -> Encoding)
-> ([AcceptCall] -> Value)
-> ([AcceptCall] -> Encoding)
-> ToJSON AcceptCall
(CreateCall -> Value)
-> (CreateCall -> Encoding)
-> ([CreateCall] -> Value)
-> ([CreateCall] -> Encoding)
-> ToJSON CreateCall
(JoinChatByInviteLink -> Value)
-> (JoinChatByInviteLink -> Encoding)
-> ([JoinChatByInviteLink] -> Value)
-> ([JoinChatByInviteLink] -> Encoding)
-> ToJSON JoinChatByInviteLink
(CheckChatInviteLink -> Value)
-> (CheckChatInviteLink -> Encoding)
-> ([CheckChatInviteLink] -> Value)
-> ([CheckChatInviteLink] -> Encoding)
-> ToJSON CheckChatInviteLink
(GenerateChatInviteLink -> Value)
-> (GenerateChatInviteLink -> Encoding)
-> ([GenerateChatInviteLink] -> Value)
-> ([GenerateChatInviteLink] -> Encoding)
-> ToJSON GenerateChatInviteLink
(DeleteFile -> Value)
-> (DeleteFile -> Encoding)
-> ([DeleteFile] -> Value)
-> ([DeleteFile] -> Encoding)
-> ToJSON DeleteFile
(ReadFilePart -> Value)
-> (ReadFilePart -> Encoding)
-> ([ReadFilePart] -> Value)
-> ([ReadFilePart] -> Encoding)
-> ToJSON ReadFilePart
(FinishFileGeneration -> Value)
-> (FinishFileGeneration -> Encoding)
-> ([FinishFileGeneration] -> Value)
-> ([FinishFileGeneration] -> Encoding)
-> ToJSON FinishFileGeneration
(SetFileGenerationProgress -> Value)
-> (SetFileGenerationProgress -> Encoding)
-> ([SetFileGenerationProgress] -> Value)
-> ([SetFileGenerationProgress] -> Encoding)
-> ToJSON SetFileGenerationProgress
(WriteGeneratedFilePart -> Value)
-> (WriteGeneratedFilePart -> Encoding)
-> ([WriteGeneratedFilePart] -> Value)
-> ([WriteGeneratedFilePart] -> Encoding)
-> ToJSON WriteGeneratedFilePart
(CancelUploadFile -> Value)
-> (CancelUploadFile -> Encoding)
-> ([CancelUploadFile] -> Value)
-> ([CancelUploadFile] -> Encoding)
-> ToJSON CancelUploadFile
(UploadFile -> Value)
-> (UploadFile -> Encoding)
-> ([UploadFile] -> Value)
-> ([UploadFile] -> Encoding)
-> ToJSON UploadFile
(CancelDownloadFile -> Value)
-> (CancelDownloadFile -> Encoding)
-> ([CancelDownloadFile] -> Value)
-> ([CancelDownloadFile] -> Encoding)
-> ToJSON CancelDownloadFile
(GetFileDownloadedPrefixSize -> Value)
-> (GetFileDownloadedPrefixSize -> Encoding)
-> ([GetFileDownloadedPrefixSize] -> Value)
-> ([GetFileDownloadedPrefixSize] -> Encoding)
-> ToJSON GetFileDownloadedPrefixSize
(DownloadFile -> Value)
-> (DownloadFile -> Encoding)
-> ([DownloadFile] -> Value)
-> ([DownloadFile] -> Encoding)
-> ToJSON DownloadFile
(SetPinnedChats -> Value)
-> (SetPinnedChats -> Encoding)
-> ([SetPinnedChats] -> Value)
-> ([SetPinnedChats] -> Encoding)
-> ToJSON SetPinnedChats
(ResetAllNotificationSettings -> Value)
-> (ResetAllNotificationSettings -> Encoding)
-> ([ResetAllNotificationSettings] -> Value)
-> ([ResetAllNotificationSettings] -> Encoding)
-> ToJSON ResetAllNotificationSettings
(SetScopeNotificationSettings -> Value)
-> (SetScopeNotificationSettings -> Encoding)
-> ([SetScopeNotificationSettings] -> Value)
-> ([SetScopeNotificationSettings] -> Encoding)
-> ToJSON SetScopeNotificationSettings
(GetScopeNotificationSettings -> Value)
-> (GetScopeNotificationSettings -> Encoding)
-> ([GetScopeNotificationSettings] -> Value)
-> ([GetScopeNotificationSettings] -> Encoding)
-> ToJSON GetScopeNotificationSettings
(GetChatNotificationSettingsExceptions -> Value)
-> (GetChatNotificationSettingsExceptions -> Encoding)
-> ([GetChatNotificationSettingsExceptions] -> Value)
-> ([GetChatNotificationSettingsExceptions] -> Encoding)
-> ToJSON GetChatNotificationSettingsExceptions
(ClearAllDraftMessages -> Value)
-> (ClearAllDraftMessages -> Encoding)
-> ([ClearAllDraftMessages] -> Value)
-> ([ClearAllDraftMessages] -> Encoding)
-> ToJSON ClearAllDraftMessages
(GetChatAdministrators -> Value)
-> (GetChatAdministrators -> Encoding)
-> ([GetChatAdministrators] -> Value)
-> ([GetChatAdministrators] -> Encoding)
-> ToJSON GetChatAdministrators
(SearchChatMembers -> Value)
-> (SearchChatMembers -> Encoding)
-> ([SearchChatMembers] -> Value)
-> ([SearchChatMembers] -> Encoding)
-> ToJSON SearchChatMembers
(GetChatMember -> Value)
-> (GetChatMember -> Encoding)
-> ([GetChatMember] -> Value)
-> ([GetChatMember] -> Encoding)
-> ToJSON GetChatMember
(TransferChatOwnership -> Value)
-> (TransferChatOwnership -> Encoding)
-> ([TransferChatOwnership] -> Value)
-> ([TransferChatOwnership] -> Encoding)
-> ToJSON TransferChatOwnership
(CanTransferOwnership -> Value)
-> (CanTransferOwnership -> Encoding)
-> ([CanTransferOwnership] -> Value)
-> ([CanTransferOwnership] -> Encoding)
-> ToJSON CanTransferOwnership
(SetChatMemberStatus -> Value)
-> (SetChatMemberStatus -> Encoding)
-> ([SetChatMemberStatus] -> Value)
-> ([SetChatMemberStatus] -> Encoding)
-> ToJSON SetChatMemberStatus
(AddChatMembers -> Value)
-> (AddChatMembers -> Encoding)
-> ([AddChatMembers] -> Value)
-> ([AddChatMembers] -> Encoding)
-> ToJSON AddChatMembers
(AddChatMember -> Value)
-> (AddChatMember -> Encoding)
-> ([AddChatMember] -> Value)
-> ([AddChatMember] -> Encoding)
-> ToJSON AddChatMember
(LeaveChat -> Value)
-> (LeaveChat -> Encoding)
-> ([LeaveChat] -> Value)
-> ([LeaveChat] -> Encoding)
-> ToJSON LeaveChat
(JoinChat -> Value)
-> (JoinChat -> Encoding)
-> ([JoinChat] -> Value)
-> ([JoinChat] -> Encoding)
-> ToJSON JoinChat
(UnpinChatMessage -> Value)
-> (UnpinChatMessage -> Encoding)
-> ([UnpinChatMessage] -> Value)
-> ([UnpinChatMessage] -> Encoding)
-> ToJSON UnpinChatMessage
(PinChatMessage -> Value)
-> (PinChatMessage -> Encoding)
-> ([PinChatMessage] -> Value)
-> ([PinChatMessage] -> Encoding)
-> ToJSON PinChatMessage
(SetChatSlowModeDelay -> Value)
-> (SetChatSlowModeDelay -> Encoding)
-> ([SetChatSlowModeDelay] -> Value)
-> ([SetChatSlowModeDelay] -> Encoding)
-> ToJSON SetChatSlowModeDelay
(SetChatLocation -> Value)
-> (SetChatLocation -> Encoding)
-> ([SetChatLocation] -> Value)
-> ([SetChatLocation] -> Encoding)
-> ToJSON SetChatLocation
(SetChatDiscussionGroup -> Value)
-> (SetChatDiscussionGroup -> Encoding)
-> ([SetChatDiscussionGroup] -> Value)
-> ([SetChatDiscussionGroup] -> Encoding)
-> ToJSON SetChatDiscussionGroup
(SetChatDescription -> Value)
-> (SetChatDescription -> Encoding)
-> ([SetChatDescription] -> Value)
-> ([SetChatDescription] -> Encoding)
-> ToJSON SetChatDescription
(SetChatClientData -> Value)
-> (SetChatClientData -> Encoding)
-> ([SetChatClientData] -> Value)
-> ([SetChatClientData] -> Encoding)
-> ToJSON SetChatClientData
(ToggleChatDefaultDisableNotification -> Value)
-> (ToggleChatDefaultDisableNotification -> Encoding)
-> ([ToggleChatDefaultDisableNotification] -> Value)
-> ([ToggleChatDefaultDisableNotification] -> Encoding)
-> ToJSON ToggleChatDefaultDisableNotification
(ToggleChatIsMarkedAsUnread -> Value)
-> (ToggleChatIsMarkedAsUnread -> Encoding)
-> ([ToggleChatIsMarkedAsUnread] -> Value)
-> ([ToggleChatIsMarkedAsUnread] -> Encoding)
-> ToJSON ToggleChatIsMarkedAsUnread
(ToggleChatIsPinned -> Value)
-> (ToggleChatIsPinned -> Encoding)
-> ([ToggleChatIsPinned] -> Value)
-> ([ToggleChatIsPinned] -> Encoding)
-> ToJSON ToggleChatIsPinned
(SetChatNotificationSettings -> Value)
-> (SetChatNotificationSettings -> Encoding)
-> ([SetChatNotificationSettings] -> Value)
-> ([SetChatNotificationSettings] -> Encoding)
-> ToJSON SetChatNotificationSettings
(SetChatDraftMessage -> Value)
-> (SetChatDraftMessage -> Encoding)
-> ([SetChatDraftMessage] -> Value)
-> ([SetChatDraftMessage] -> Encoding)
-> ToJSON SetChatDraftMessage
(SetChatPermissions -> Value)
-> (SetChatPermissions -> Encoding)
-> ([SetChatPermissions] -> Value)
-> ([SetChatPermissions] -> Encoding)
-> ToJSON SetChatPermissions
(SetChatPhoto -> Value)
-> (SetChatPhoto -> Encoding)
-> ([SetChatPhoto] -> Value)
-> ([SetChatPhoto] -> Encoding)
-> ToJSON SetChatPhoto
(SetChatTitle -> Value)
-> (SetChatTitle -> Encoding)
-> ([SetChatTitle] -> Value)
-> ([SetChatTitle] -> Encoding)
-> ToJSON SetChatTitle
(SetChatChatList -> Value)
-> (SetChatChatList -> Encoding)
-> ([SetChatChatList] -> Value)
-> ([SetChatChatList] -> Encoding)
-> ToJSON SetChatChatList
(UpgradeBasicGroupChatToSupergroupChat -> Value)
-> (UpgradeBasicGroupChatToSupergroupChat -> Encoding)
-> ([UpgradeBasicGroupChatToSupergroupChat] -> Value)
-> ([UpgradeBasicGroupChatToSupergroupChat] -> Encoding)
-> ToJSON UpgradeBasicGroupChatToSupergroupChat
(CreateNewSecretChat -> Value)
-> (CreateNewSecretChat -> Encoding)
-> ([CreateNewSecretChat] -> Value)
-> ([CreateNewSecretChat] -> Encoding)
-> ToJSON CreateNewSecretChat
(CreateNewSupergroupChat -> Value)
-> (CreateNewSupergroupChat -> Encoding)
-> ([CreateNewSupergroupChat] -> Value)
-> ([CreateNewSupergroupChat] -> Encoding)
-> ToJSON CreateNewSupergroupChat
(CreateNewBasicGroupChat -> Value)
-> (CreateNewBasicGroupChat -> Encoding)
-> ([CreateNewBasicGroupChat] -> Value)
-> ([CreateNewBasicGroupChat] -> Encoding)
-> ToJSON CreateNewBasicGroupChat
(CreateSecretChat -> Value)
-> (CreateSecretChat -> Encoding)
-> ([CreateSecretChat] -> Value)
-> ([CreateSecretChat] -> Encoding)
-> ToJSON CreateSecretChat
(CreateSupergroupChat -> Value)
-> (CreateSupergroupChat -> Encoding)
-> ([CreateSupergroupChat] -> Value)
-> ([CreateSupergroupChat] -> Encoding)
-> ToJSON CreateSupergroupChat
(CreateBasicGroupChat -> Value)
-> (CreateBasicGroupChat -> Encoding)
-> ([CreateBasicGroupChat] -> Value)
-> ([CreateBasicGroupChat] -> Encoding)
-> ToJSON CreateBasicGroupChat
(CreatePrivateChat -> Value)
-> (CreatePrivateChat -> Encoding)
-> ([CreatePrivateChat] -> Value)
-> ([CreatePrivateChat] -> Encoding)
-> ToJSON CreatePrivateChat
(ReadAllChatMentions -> Value)
-> (ReadAllChatMentions -> Encoding)
-> ([ReadAllChatMentions] -> Value)
-> ([ReadAllChatMentions] -> Encoding)
-> ToJSON ReadAllChatMentions
(OpenMessageContent -> Value)
-> (OpenMessageContent -> Encoding)
-> ([OpenMessageContent] -> Value)
-> ([OpenMessageContent] -> Encoding)
-> ToJSON OpenMessageContent
(ViewMessages -> Value)
-> (ViewMessages -> Encoding)
-> ([ViewMessages] -> Value)
-> ([ViewMessages] -> Encoding)
-> ToJSON ViewMessages
(CloseChat -> Value)
-> (CloseChat -> Encoding)
-> ([CloseChat] -> Value)
-> ([CloseChat] -> Encoding)
-> ToJSON CloseChat
(OpenChat -> Value)
-> (OpenChat -> Encoding)
-> ([OpenChat] -> Value)
-> ([OpenChat] -> Encoding)
-> ToJSON OpenChat
(SendChatAction -> Value)
-> (SendChatAction -> Encoding)
-> ([SendChatAction] -> Value)
-> ([SendChatAction] -> Encoding)
-> ToJSON SendChatAction
(DeleteChatReplyMarkup -> Value)
-> (DeleteChatReplyMarkup -> Encoding)
-> ([DeleteChatReplyMarkup] -> Value)
-> ([DeleteChatReplyMarkup] -> Encoding)
-> ToJSON DeleteChatReplyMarkup
(GetInlineGameHighScores -> Value)
-> (GetInlineGameHighScores -> Encoding)
-> ([GetInlineGameHighScores] -> Value)
-> ([GetInlineGameHighScores] -> Encoding)
-> ToJSON GetInlineGameHighScores
(GetGameHighScores -> Value)
-> (GetGameHighScores -> Encoding)
-> ([GetGameHighScores] -> Value)
-> ([GetGameHighScores] -> Encoding)
-> ToJSON GetGameHighScores
(SetInlineGameScore -> Value)
-> (SetInlineGameScore -> Encoding)
-> ([SetInlineGameScore] -> Value)
-> ([SetInlineGameScore] -> Encoding)
-> ToJSON SetInlineGameScore
(SetGameScore -> Value)
-> (SetGameScore -> Encoding)
-> ([SetGameScore] -> Value)
-> ([SetGameScore] -> Encoding)
-> ToJSON SetGameScore
(AnswerPreCheckoutQuery -> Value)
-> (AnswerPreCheckoutQuery -> Encoding)
-> ([AnswerPreCheckoutQuery] -> Value)
-> ([AnswerPreCheckoutQuery] -> Encoding)
-> ToJSON AnswerPreCheckoutQuery
(AnswerShippingQuery -> Value)
-> (AnswerShippingQuery -> Encoding)
-> ([AnswerShippingQuery] -> Value)
-> ([AnswerShippingQuery] -> Encoding)
-> ToJSON AnswerShippingQuery
(AnswerCallbackQuery -> Value)
-> (AnswerCallbackQuery -> Encoding)
-> ([AnswerCallbackQuery] -> Value)
-> ([AnswerCallbackQuery] -> Encoding)
-> ToJSON AnswerCallbackQuery
(GetCallbackQueryAnswer -> Value)
-> (GetCallbackQueryAnswer -> Encoding)
-> ([GetCallbackQueryAnswer] -> Value)
-> ([GetCallbackQueryAnswer] -> Encoding)
-> ToJSON GetCallbackQueryAnswer
(AnswerInlineQuery -> Value)
-> (AnswerInlineQuery -> Encoding)
-> ([AnswerInlineQuery] -> Value)
-> ([AnswerInlineQuery] -> Encoding)
-> ToJSON AnswerInlineQuery
(GetInlineQueryResults -> Value)
-> (GetInlineQueryResults -> Encoding)
-> ([GetInlineQueryResults] -> Value)
-> ([GetInlineQueryResults] -> Encoding)
-> ToJSON GetInlineQueryResults
(GetLoginUrl -> Value)
-> (GetLoginUrl -> Encoding)
-> ([GetLoginUrl] -> Value)
-> ([GetLoginUrl] -> Encoding)
-> ToJSON GetLoginUrl
(GetLoginUrlInfo -> Value)
-> (GetLoginUrlInfo -> Encoding)
-> ([GetLoginUrlInfo] -> Value)
-> ([GetLoginUrlInfo] -> Encoding)
-> ToJSON GetLoginUrlInfo
(StopPoll -> Value)
-> (StopPoll -> Encoding)
-> ([StopPoll] -> Value)
-> ([StopPoll] -> Encoding)
-> ToJSON StopPoll
(GetPollVoters -> Value)
-> (GetPollVoters -> Encoding)
-> ([GetPollVoters] -> Value)
-> ([GetPollVoters] -> Encoding)
-> ToJSON GetPollVoters
(SetPollAnswer -> Value)
-> (SetPollAnswer -> Encoding)
-> ([SetPollAnswer] -> Value)
-> ([SetPollAnswer] -> Encoding)
-> ToJSON SetPollAnswer
(GetJsonString -> Value)
-> (GetJsonString -> Encoding)
-> ([GetJsonString] -> Value)
-> ([GetJsonString] -> Encoding)
-> ToJSON GetJsonString
(GetJsonValue -> Value)
-> (GetJsonValue -> Encoding)
-> ([GetJsonValue] -> Value)
-> ([GetJsonValue] -> Encoding)
-> ToJSON GetJsonValue
(GetLanguagePackString -> Value)
-> (GetLanguagePackString -> Encoding)
-> ([GetLanguagePackString] -> Value)
-> ([GetLanguagePackString] -> Encoding)
-> ToJSON GetLanguagePackString
(CleanFileName -> Value)
-> (CleanFileName -> Encoding)
-> ([CleanFileName] -> Value)
-> ([CleanFileName] -> Encoding)
-> ToJSON CleanFileName
(GetFileExtension -> Value)
-> (GetFileExtension -> Encoding)
-> ([GetFileExtension] -> Value)
-> ([GetFileExtension] -> Encoding)
-> ToJSON GetFileExtension
(GetFileMimeType -> Value)
-> (GetFileMimeType -> Encoding)
-> ([GetFileMimeType] -> Value)
-> ([GetFileMimeType] -> Encoding)
-> ToJSON GetFileMimeType
(GetMarkdownText -> Value)
-> (GetMarkdownText -> Encoding)
-> ([GetMarkdownText] -> Value)
-> ([GetMarkdownText] -> Encoding)
-> ToJSON GetMarkdownText
(ParseMarkdown -> Value)
-> (ParseMarkdown -> Encoding)
-> ([ParseMarkdown] -> Value)
-> ([ParseMarkdown] -> Encoding)
-> ToJSON ParseMarkdown
(ParseTextEntities -> Value)
-> (ParseTextEntities -> Encoding)
-> ([ParseTextEntities] -> Value)
-> ([ParseTextEntities] -> Encoding)
-> ToJSON ParseTextEntities
(GetTextEntities -> Value)
-> (GetTextEntities -> Encoding)
-> ([GetTextEntities] -> Value)
-> ([GetTextEntities] -> Encoding)
-> ToJSON GetTextEntities
(EditMessageSchedulingState -> Value)
-> (EditMessageSchedulingState -> Encoding)
-> ([EditMessageSchedulingState] -> Value)
-> ([EditMessageSchedulingState] -> Encoding)
-> ToJSON EditMessageSchedulingState
(EditInlineMessageReplyMarkup -> Value)
-> (EditInlineMessageReplyMarkup -> Encoding)
-> ([EditInlineMessageReplyMarkup] -> Value)
-> ([EditInlineMessageReplyMarkup] -> Encoding)
-> ToJSON EditInlineMessageReplyMarkup
(EditInlineMessageCaption -> Value)
-> (EditInlineMessageCaption -> Encoding)
-> ([EditInlineMessageCaption] -> Value)
-> ([EditInlineMessageCaption] -> Encoding)
-> ToJSON EditInlineMessageCaption
(EditInlineMessageMedia -> Value)
-> (EditInlineMessageMedia -> Encoding)
-> ([EditInlineMessageMedia] -> Value)
-> ([EditInlineMessageMedia] -> Encoding)
-> ToJSON EditInlineMessageMedia
(EditInlineMessageLiveLocation -> Value)
-> (EditInlineMessageLiveLocation -> Encoding)
-> ([EditInlineMessageLiveLocation] -> Value)
-> ([EditInlineMessageLiveLocation] -> Encoding)
-> ToJSON EditInlineMessageLiveLocation
(EditInlineMessageText -> Value)
-> (EditInlineMessageText -> Encoding)
-> ([EditInlineMessageText] -> Value)
-> ([EditInlineMessageText] -> Encoding)
-> ToJSON EditInlineMessageText
(EditMessageReplyMarkup -> Value)
-> (EditMessageReplyMarkup -> Encoding)
-> ([EditMessageReplyMarkup] -> Value)
-> ([EditMessageReplyMarkup] -> Encoding)
-> ToJSON EditMessageReplyMarkup
(EditMessageCaption -> Value)
-> (EditMessageCaption -> Encoding)
-> ([EditMessageCaption] -> Value)
-> ([EditMessageCaption] -> Encoding)
-> ToJSON EditMessageCaption
(EditMessageMedia -> Value)
-> (EditMessageMedia -> Encoding)
-> ([EditMessageMedia] -> Value)
-> ([EditMessageMedia] -> Encoding)
-> ToJSON EditMessageMedia
(EditMessageLiveLocation -> Value)
-> (EditMessageLiveLocation -> Encoding)
-> ([EditMessageLiveLocation] -> Value)
-> ([EditMessageLiveLocation] -> Encoding)
-> ToJSON EditMessageLiveLocation
(EditMessageText -> Value)
-> (EditMessageText -> Encoding)
-> ([EditMessageText] -> Value)
-> ([EditMessageText] -> Encoding)
-> ToJSON EditMessageText
(DeleteChatMessagesFromUser -> Value)
-> (DeleteChatMessagesFromUser -> Encoding)
-> ([DeleteChatMessagesFromUser] -> Value)
-> ([DeleteChatMessagesFromUser] -> Encoding)
-> ToJSON DeleteChatMessagesFromUser
(DeleteMessages -> Value)
-> (DeleteMessages -> Encoding)
-> ([DeleteMessages] -> Value)
-> ([DeleteMessages] -> Encoding)
-> ToJSON DeleteMessages
(AddLocalMessage -> Value)
-> (AddLocalMessage -> Encoding)
-> ([AddLocalMessage] -> Value)
-> ([AddLocalMessage] -> Encoding)
-> ToJSON AddLocalMessage
(SendChatScreenshotTakenNotification -> Value)
-> (SendChatScreenshotTakenNotification -> Encoding)
-> ([SendChatScreenshotTakenNotification] -> Value)
-> ([SendChatScreenshotTakenNotification] -> Encoding)
-> ToJSON SendChatScreenshotTakenNotification
(SendChatSetTtlMessage -> Value)
-> (SendChatSetTtlMessage -> Encoding)
-> ([SendChatSetTtlMessage] -> Value)
-> ([SendChatSetTtlMessage] -> Encoding)
-> ToJSON SendChatSetTtlMessage
(ResendMessages -> Value)
-> (ResendMessages -> Encoding)
-> ([ResendMessages] -> Value)
-> ([ResendMessages] -> Encoding)
-> ToJSON ResendMessages
(ForwardMessages -> Value)
-> (ForwardMessages -> Encoding)
-> ([ForwardMessages] -> Value)
-> ([ForwardMessages] -> Encoding)
-> ToJSON ForwardMessages
(SendInlineQueryResultMessage -> Value)
-> (SendInlineQueryResultMessage -> Encoding)
-> ([SendInlineQueryResultMessage] -> Value)
-> ([SendInlineQueryResultMessage] -> Encoding)
-> ToJSON SendInlineQueryResultMessage
(SendBotStartMessage -> Value)
-> (SendBotStartMessage -> Encoding)
-> ([SendBotStartMessage] -> Value)
-> ([SendBotStartMessage] -> Encoding)
-> ToJSON SendBotStartMessage
(SendMessageAlbum -> Value)
-> (SendMessageAlbum -> Encoding)
-> ([SendMessageAlbum] -> Value)
-> ([SendMessageAlbum] -> Encoding)
-> ToJSON SendMessageAlbum
(SendMessage -> Value)
-> (SendMessage -> Encoding)
-> ([SendMessage] -> Value)
-> ([SendMessage] -> Encoding)
-> ToJSON SendMessage
(GetMessageLinkInfo -> Value)
-> (GetMessageLinkInfo -> Encoding)
-> ([GetMessageLinkInfo] -> Value)
-> ([GetMessageLinkInfo] -> Encoding)
-> ToJSON GetMessageLinkInfo
(GetMessageLink -> Value)
-> (GetMessageLink -> Encoding)
-> ([GetMessageLink] -> Value)
-> ([GetMessageLink] -> Encoding)
-> ToJSON GetMessageLink
(GetPublicMessageLink -> Value)
-> (GetPublicMessageLink -> Encoding)
-> ([GetPublicMessageLink] -> Value)
-> ([GetPublicMessageLink] -> Encoding)
-> ToJSON GetPublicMessageLink
(RemoveNotificationGroup -> Value)
-> (RemoveNotificationGroup -> Encoding)
-> ([RemoveNotificationGroup] -> Value)
-> ([RemoveNotificationGroup] -> Encoding)
-> ToJSON RemoveNotificationGroup
(RemoveNotification -> Value)
-> (RemoveNotification -> Encoding)
-> ([RemoveNotification] -> Value)
-> ([RemoveNotification] -> Encoding)
-> ToJSON RemoveNotification
(GetChatScheduledMessages -> Value)
-> (GetChatScheduledMessages -> Encoding)
-> ([GetChatScheduledMessages] -> Value)
-> ([GetChatScheduledMessages] -> Encoding)
-> ToJSON GetChatScheduledMessages
(GetChatMessageCount -> Value)
-> (GetChatMessageCount -> Encoding)
-> ([GetChatMessageCount] -> Value)
-> ([GetChatMessageCount] -> Encoding)
-> ToJSON GetChatMessageCount
(GetChatMessageByDate -> Value)
-> (GetChatMessageByDate -> Encoding)
-> ([GetChatMessageByDate] -> Value)
-> ([GetChatMessageByDate] -> Encoding)
-> ToJSON GetChatMessageByDate
(GetActiveLiveLocationMessages -> Value)
-> (GetActiveLiveLocationMessages -> Encoding)
-> ([GetActiveLiveLocationMessages] -> Value)
-> ([GetActiveLiveLocationMessages] -> Encoding)
-> ToJSON GetActiveLiveLocationMessages
(SearchChatRecentLocationMessages -> Value)
-> (SearchChatRecentLocationMessages -> Encoding)
-> ([SearchChatRecentLocationMessages] -> Value)
-> ([SearchChatRecentLocationMessages] -> Encoding)
-> ToJSON SearchChatRecentLocationMessages
(SearchCallMessages -> Value)
-> (SearchCallMessages -> Encoding)
-> ([SearchCallMessages] -> Value)
-> ([SearchCallMessages] -> Encoding)
-> ToJSON SearchCallMessages
(SearchSecretMessages -> Value)
-> (SearchSecretMessages -> Encoding)
-> ([SearchSecretMessages] -> Value)
-> ([SearchSecretMessages] -> Encoding)
-> ToJSON SearchSecretMessages
(SearchMessages -> Value)
-> (SearchMessages -> Encoding)
-> ([SearchMessages] -> Value)
-> ([SearchMessages] -> Encoding)
-> ToJSON SearchMessages
(SearchChatMessages -> Value)
-> (SearchChatMessages -> Encoding)
-> ([SearchChatMessages] -> Value)
-> ([SearchChatMessages] -> Encoding)
-> ToJSON SearchChatMessages
(DeleteChatHistory -> Value)
-> (DeleteChatHistory -> Encoding)
-> ([DeleteChatHistory] -> Value)
-> ([DeleteChatHistory] -> Encoding)
-> ToJSON DeleteChatHistory
(GetChatHistory -> Value)
-> (GetChatHistory -> Encoding)
-> ([GetChatHistory] -> Value)
-> ([GetChatHistory] -> Encoding)
-> ToJSON GetChatHistory
(GetGroupsInCommon -> Value)
-> (GetGroupsInCommon -> Encoding)
-> ([GetGroupsInCommon] -> Value)
-> ([GetGroupsInCommon] -> Encoding)
-> ToJSON GetGroupsInCommon
(GetInactiveSupergroupChats -> Value)
-> (GetInactiveSupergroupChats -> Encoding)
-> ([GetInactiveSupergroupChats] -> Value)
-> ([GetInactiveSupergroupChats] -> Encoding)
-> ToJSON GetInactiveSupergroupChats
(GetSuitableDiscussionChats -> Value)
-> (GetSuitableDiscussionChats -> Encoding)
-> ([GetSuitableDiscussionChats] -> Value)
-> ([GetSuitableDiscussionChats] -> Encoding)
-> ToJSON GetSuitableDiscussionChats
(CheckCreatedPublicChatsLimit -> Value)
-> (CheckCreatedPublicChatsLimit -> Encoding)
-> ([CheckCreatedPublicChatsLimit] -> Value)
-> ([CheckCreatedPublicChatsLimit] -> Encoding)
-> ToJSON CheckCreatedPublicChatsLimit
(GetCreatedPublicChats -> Value)
-> (GetCreatedPublicChats -> Encoding)
-> ([GetCreatedPublicChats] -> Value)
-> ([GetCreatedPublicChats] -> Encoding)
-> ToJSON GetCreatedPublicChats
(CheckChatUsername -> Value)
-> (CheckChatUsername -> Encoding)
-> ([CheckChatUsername] -> Value)
-> ([CheckChatUsername] -> Encoding)
-> ToJSON CheckChatUsername
(ClearRecentlyFoundChats -> Value)
-> (ClearRecentlyFoundChats -> Encoding)
-> ([ClearRecentlyFoundChats] -> Value)
-> ([ClearRecentlyFoundChats] -> Encoding)
-> ToJSON ClearRecentlyFoundChats
(RemoveRecentlyFoundChat -> Value)
-> (RemoveRecentlyFoundChat -> Encoding)
-> ([RemoveRecentlyFoundChat] -> Value)
-> ([RemoveRecentlyFoundChat] -> Encoding)
-> ToJSON RemoveRecentlyFoundChat
(AddRecentlyFoundChat -> Value)
-> (AddRecentlyFoundChat -> Encoding)
-> ([AddRecentlyFoundChat] -> Value)
-> ([AddRecentlyFoundChat] -> Encoding)
-> ToJSON AddRecentlyFoundChat
(RemoveTopChat -> Value)
-> (RemoveTopChat -> Encoding)
-> ([RemoveTopChat] -> Value)
-> ([RemoveTopChat] -> Encoding)
-> ToJSON RemoveTopChat
(GetTopChats -> Value)
-> (GetTopChats -> Encoding)
-> ([GetTopChats] -> Value)
-> ([GetTopChats] -> Encoding)
-> ToJSON GetTopChats
(SearchChatsNearby -> Value)
-> (SearchChatsNearby -> Encoding)
-> ([SearchChatsNearby] -> Value)
-> ([SearchChatsNearby] -> Encoding)
-> ToJSON SearchChatsNearby
(SearchChatsOnServer -> Value)
-> (SearchChatsOnServer -> Encoding)
-> ([SearchChatsOnServer] -> Value)
-> ([SearchChatsOnServer] -> Encoding)
-> ToJSON SearchChatsOnServer
(SearchChats -> Value)
-> (SearchChats -> Encoding)
-> ([SearchChats] -> Value)
-> ([SearchChats] -> Encoding)
-> ToJSON SearchChats
(SearchPublicChats -> Value)
-> (SearchPublicChats -> Encoding)
-> ([SearchPublicChats] -> Value)
-> ([SearchPublicChats] -> Encoding)
-> ToJSON SearchPublicChats
(SearchPublicChat -> Value)
-> (SearchPublicChat -> Encoding)
-> ([SearchPublicChat] -> Value)
-> ([SearchPublicChat] -> Encoding)
-> ToJSON SearchPublicChat
(GetChats -> Value)
-> (GetChats -> Encoding)
-> ([GetChats] -> Value)
-> ([GetChats] -> Encoding)
-> ToJSON GetChats
(GetRemoteFile -> Value)
-> (GetRemoteFile -> Encoding)
-> ([GetRemoteFile] -> Value)
-> ([GetRemoteFile] -> Encoding)
-> ToJSON GetRemoteFile
(GetFile -> Value)
-> (GetFile -> Encoding)
-> ([GetFile] -> Value)
-> ([GetFile] -> Encoding)
-> ToJSON GetFile
(GetMessages -> Value)
-> (GetMessages -> Encoding)
-> ([GetMessages] -> Value)
-> ([GetMessages] -> Encoding)
-> ToJSON GetMessages
(GetChatPinnedMessage -> Value)
-> (GetChatPinnedMessage -> Encoding)
-> ([GetChatPinnedMessage] -> Value)
-> ([GetChatPinnedMessage] -> Encoding)
-> ToJSON GetChatPinnedMessage
(GetRepliedMessage -> Value)
-> (GetRepliedMessage -> Encoding)
-> ([GetRepliedMessage] -> Value)
-> ([GetRepliedMessage] -> Encoding)
-> ToJSON GetRepliedMessage
(GetMessageLocally -> Value)
-> (GetMessageLocally -> Encoding)
-> ([GetMessageLocally] -> Value)
-> ([GetMessageLocally] -> Encoding)
-> ToJSON GetMessageLocally
(GetMessage -> Value)
-> (GetMessage -> Encoding)
-> ([GetMessage] -> Value)
-> ([GetMessage] -> Encoding)
-> ToJSON GetMessage
(GetChat -> Value)
-> (GetChat -> Encoding)
-> ([GetChat] -> Value)
-> ([GetChat] -> Encoding)
-> ToJSON GetChat
(GetSecretChat -> Value)
-> (GetSecretChat -> Encoding)
-> ([GetSecretChat] -> Value)
-> ([GetSecretChat] -> Encoding)
-> ToJSON GetSecretChat
(GetSupergroupFullInfo -> Value)
-> (GetSupergroupFullInfo -> Encoding)
-> ([GetSupergroupFullInfo] -> Value)
-> ([GetSupergroupFullInfo] -> Encoding)
-> ToJSON GetSupergroupFullInfo
(GetSupergroup -> Value)
-> (GetSupergroup -> Encoding)
-> ([GetSupergroup] -> Value)
-> ([GetSupergroup] -> Encoding)
-> ToJSON GetSupergroup
(GetBasicGroupFullInfo -> Value)
-> (GetBasicGroupFullInfo -> Encoding)
-> ([GetBasicGroupFullInfo] -> Value)
-> ([GetBasicGroupFullInfo] -> Encoding)
-> ToJSON GetBasicGroupFullInfo
(GetBasicGroup -> Value)
-> (GetBasicGroup -> Encoding)
-> ([GetBasicGroup] -> Value)
-> ([GetBasicGroup] -> Encoding)
-> ToJSON GetBasicGroup
(GetUserFullInfo -> Value)
-> (GetUserFullInfo -> Encoding)
-> ([GetUserFullInfo] -> Value)
-> ([GetUserFullInfo] -> Encoding)
-> ToJSON GetUserFullInfo
(GetUser -> Value)
-> (GetUser -> Encoding)
-> ([GetUser] -> Value)
-> ([GetUser] -> Encoding)
-> ToJSON GetUser
(GetMe -> Value)
-> (GetMe -> Encoding)
-> ([GetMe] -> Value)
-> ([GetMe] -> Encoding)
-> ToJSON GetMe
(GetTemporaryPasswordState -> Value)
-> (GetTemporaryPasswordState -> Encoding)
-> ([GetTemporaryPasswordState] -> Value)
-> ([GetTemporaryPasswordState] -> Encoding)
-> ToJSON GetTemporaryPasswordState
(CreateTemporaryPassword -> Value)
-> (CreateTemporaryPassword -> Encoding)
-> ([CreateTemporaryPassword] -> Value)
-> ([CreateTemporaryPassword] -> Encoding)
-> ToJSON CreateTemporaryPassword
(RecoverPassword -> Value)
-> (RecoverPassword -> Encoding)
-> ([RecoverPassword] -> Value)
-> ([RecoverPassword] -> Encoding)
-> ToJSON RecoverPassword
(RequestPasswordRecovery -> Value)
-> (RequestPasswordRecovery -> Encoding)
-> ([RequestPasswordRecovery] -> Value)
-> ([RequestPasswordRecovery] -> Encoding)
-> ToJSON RequestPasswordRecovery
(ResendRecoveryEmailAddressCode -> Value)
-> (ResendRecoveryEmailAddressCode -> Encoding)
-> ([ResendRecoveryEmailAddressCode] -> Value)
-> ([ResendRecoveryEmailAddressCode] -> Encoding)
-> ToJSON ResendRecoveryEmailAddressCode
(CheckRecoveryEmailAddressCode -> Value)
-> (CheckRecoveryEmailAddressCode -> Encoding)
-> ([CheckRecoveryEmailAddressCode] -> Value)
-> ([CheckRecoveryEmailAddressCode] -> Encoding)
-> ToJSON CheckRecoveryEmailAddressCode
(SetRecoveryEmailAddress -> Value)
-> (SetRecoveryEmailAddress -> Encoding)
-> ([SetRecoveryEmailAddress] -> Value)
-> ([SetRecoveryEmailAddress] -> Encoding)
-> ToJSON SetRecoveryEmailAddress
(GetRecoveryEmailAddress -> Value)
-> (GetRecoveryEmailAddress -> Encoding)
-> ([GetRecoveryEmailAddress] -> Value)
-> ([GetRecoveryEmailAddress] -> Encoding)
-> ToJSON GetRecoveryEmailAddress
(SetPassword -> Value)
-> (SetPassword -> Encoding)
-> ([SetPassword] -> Value)
-> ([SetPassword] -> Encoding)
-> ToJSON SetPassword
(GetPasswordState -> Value)
-> (GetPasswordState -> Encoding)
-> ([GetPasswordState] -> Value)
-> ([GetPasswordState] -> Encoding)
-> ToJSON GetPasswordState
(SetDatabaseEncryptionKey -> Value)
-> (SetDatabaseEncryptionKey -> Encoding)
-> ([SetDatabaseEncryptionKey] -> Value)
-> ([SetDatabaseEncryptionKey] -> Encoding)
-> ToJSON SetDatabaseEncryptionKey
(GetCurrentState -> Value)
-> (GetCurrentState -> Encoding)
-> ([GetCurrentState] -> Value)
-> ([GetCurrentState] -> Encoding)
-> ToJSON GetCurrentState
(ConfirmQrCodeAuthentication -> Value)
-> (ConfirmQrCodeAuthentication -> Encoding)
-> ([ConfirmQrCodeAuthentication] -> Value)
-> ([ConfirmQrCodeAuthentication] -> Encoding)
-> ToJSON ConfirmQrCodeAuthentication
(Destroy -> Value)
-> (Destroy -> Encoding)
-> ([Destroy] -> Value)
-> ([Destroy] -> Encoding)
-> ToJSON Destroy
(Close -> Value)
-> (Close -> Encoding)
-> ([Close] -> Value)
-> ([Close] -> Encoding)
-> ToJSON Close
(LogOut -> Value)
-> (LogOut -> Encoding)
-> ([LogOut] -> Value)
-> ([LogOut] -> Encoding)
-> ToJSON LogOut
(CheckAuthenticationBotToken -> Value)
-> (CheckAuthenticationBotToken -> Encoding)
-> ([CheckAuthenticationBotToken] -> Value)
-> ([CheckAuthenticationBotToken] -> Encoding)
-> ToJSON CheckAuthenticationBotToken
(RecoverAuthenticationPassword -> Value)
-> (RecoverAuthenticationPassword -> Encoding)
-> ([RecoverAuthenticationPassword] -> Value)
-> ([RecoverAuthenticationPassword] -> Encoding)
-> ToJSON RecoverAuthenticationPassword
(RequestAuthenticationPasswordRecovery -> Value)
-> (RequestAuthenticationPasswordRecovery -> Encoding)
-> ([RequestAuthenticationPasswordRecovery] -> Value)
-> ([RequestAuthenticationPasswordRecovery] -> Encoding)
-> ToJSON RequestAuthenticationPasswordRecovery
(CheckAuthenticationPassword -> Value)
-> (CheckAuthenticationPassword -> Encoding)
-> ([CheckAuthenticationPassword] -> Value)
-> ([CheckAuthenticationPassword] -> Encoding)
-> ToJSON CheckAuthenticationPassword
(RegisterUser -> Value)
-> (RegisterUser -> Encoding)
-> ([RegisterUser] -> Value)
-> ([RegisterUser] -> Encoding)
-> ToJSON RegisterUser
(RequestQrCodeAuthentication -> Value)
-> (RequestQrCodeAuthentication -> Encoding)
-> ([RequestQrCodeAuthentication] -> Value)
-> ([RequestQrCodeAuthentication] -> Encoding)
-> ToJSON RequestQrCodeAuthentication
(CheckAuthenticationCode -> Value)
-> (CheckAuthenticationCode -> Encoding)
-> ([CheckAuthenticationCode] -> Value)
-> ([CheckAuthenticationCode] -> Encoding)
-> ToJSON CheckAuthenticationCode
(ResendAuthenticationCode -> Value)
-> (ResendAuthenticationCode -> Encoding)
-> ([ResendAuthenticationCode] -> Value)
-> ([ResendAuthenticationCode] -> Encoding)
-> ToJSON ResendAuthenticationCode
(SetAuthenticationPhoneNumber -> Value)
-> (SetAuthenticationPhoneNumber -> Encoding)
-> ([SetAuthenticationPhoneNumber] -> Value)
-> ([SetAuthenticationPhoneNumber] -> Encoding)
-> ToJSON SetAuthenticationPhoneNumber
(CheckDatabaseEncryptionKey -> Value)
-> (CheckDatabaseEncryptionKey -> Encoding)
-> ([CheckDatabaseEncryptionKey] -> Value)
-> ([CheckDatabaseEncryptionKey] -> Encoding)
-> ToJSON CheckDatabaseEncryptionKey
(SetTdlibParameters -> Value)
-> (SetTdlibParameters -> Encoding)
-> ([SetTdlibParameters] -> Value)
-> ([SetTdlibParameters] -> Encoding)
-> ToJSON SetTdlibParameters
(GetAuthorizationState -> Value)
-> (GetAuthorizationState -> Encoding)
-> ([GetAuthorizationState] -> Value)
-> ([GetAuthorizationState] -> Encoding)
-> ToJSON GetAuthorizationState
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
toEncodingList :: [GetAuthorizationState] -> Encoding
$ctoEncodingList :: [GetAuthorizationState] -> Encoding
toJSONList :: [GetAuthorizationState] -> Value
$ctoJSONList :: [GetAuthorizationState] -> Value
toEncoding :: GetAuthorizationState -> Encoding
$ctoEncoding :: GetAuthorizationState -> Encoding
toJSON :: GetAuthorizationState -> Value
$ctoJSON :: GetAuthorizationState -> Value
parseJSONList :: Value -> Parser [GetAuthorizationState]
$cparseJSONList :: Value -> Parser [GetAuthorizationState]
parseJSON :: Value -> Parser GetAuthorizationState
$cparseJSON :: Value -> Parser GetAuthorizationState
toEncodingList :: [SetTdlibParameters] -> Encoding
$ctoEncodingList :: [SetTdlibParameters] -> Encoding
toJSONList :: [SetTdlibParameters] -> Value
$ctoJSONList :: [SetTdlibParameters] -> Value
toEncoding :: SetTdlibParameters -> Encoding
$ctoEncoding :: SetTdlibParameters -> Encoding
toJSON :: SetTdlibParameters -> Value
$ctoJSON :: SetTdlibParameters -> Value
parseJSONList :: Value -> Parser [SetTdlibParameters]
$cparseJSONList :: Value -> Parser [SetTdlibParameters]
parseJSON :: Value -> Parser SetTdlibParameters
$cparseJSON :: Value -> Parser SetTdlibParameters
toEncodingList :: [CheckDatabaseEncryptionKey] -> Encoding
$ctoEncodingList :: [CheckDatabaseEncryptionKey] -> Encoding
toJSONList :: [CheckDatabaseEncryptionKey] -> Value
$ctoJSONList :: [CheckDatabaseEncryptionKey] -> Value
toEncoding :: CheckDatabaseEncryptionKey -> Encoding
$ctoEncoding :: CheckDatabaseEncryptionKey -> Encoding
toJSON :: CheckDatabaseEncryptionKey -> Value
$ctoJSON :: CheckDatabaseEncryptionKey -> Value
parseJSONList :: Value -> Parser [CheckDatabaseEncryptionKey]
$cparseJSONList :: Value -> Parser [CheckDatabaseEncryptionKey]
parseJSON :: Value -> Parser CheckDatabaseEncryptionKey
$cparseJSON :: Value -> Parser CheckDatabaseEncryptionKey
toEncodingList :: [SetAuthenticationPhoneNumber] -> Encoding
$ctoEncodingList :: [SetAuthenticationPhoneNumber] -> Encoding
toJSONList :: [SetAuthenticationPhoneNumber] -> Value
$ctoJSONList :: [SetAuthenticationPhoneNumber] -> Value
toEncoding :: SetAuthenticationPhoneNumber -> Encoding
$ctoEncoding :: SetAuthenticationPhoneNumber -> Encoding
toJSON :: SetAuthenticationPhoneNumber -> Value
$ctoJSON :: SetAuthenticationPhoneNumber -> Value
parseJSONList :: Value -> Parser [SetAuthenticationPhoneNumber]
$cparseJSONList :: Value -> Parser [SetAuthenticationPhoneNumber]
parseJSON :: Value -> Parser SetAuthenticationPhoneNumber
$cparseJSON :: Value -> Parser SetAuthenticationPhoneNumber
toEncodingList :: [ResendAuthenticationCode] -> Encoding
$ctoEncodingList :: [ResendAuthenticationCode] -> Encoding
toJSONList :: [ResendAuthenticationCode] -> Value
$ctoJSONList :: [ResendAuthenticationCode] -> Value
toEncoding :: ResendAuthenticationCode -> Encoding
$ctoEncoding :: ResendAuthenticationCode -> Encoding
toJSON :: ResendAuthenticationCode -> Value
$ctoJSON :: ResendAuthenticationCode -> Value
parseJSONList :: Value -> Parser [ResendAuthenticationCode]
$cparseJSONList :: Value -> Parser [ResendAuthenticationCode]
parseJSON :: Value -> Parser ResendAuthenticationCode
$cparseJSON :: Value -> Parser ResendAuthenticationCode
toEncodingList :: [CheckAuthenticationCode] -> Encoding
$ctoEncodingList :: [CheckAuthenticationCode] -> Encoding
toJSONList :: [CheckAuthenticationCode] -> Value
$ctoJSONList :: [CheckAuthenticationCode] -> Value
toEncoding :: CheckAuthenticationCode -> Encoding
$ctoEncoding :: CheckAuthenticationCode -> Encoding
toJSON :: CheckAuthenticationCode -> Value
$ctoJSON :: CheckAuthenticationCode -> Value
parseJSONList :: Value -> Parser [CheckAuthenticationCode]
$cparseJSONList :: Value -> Parser [CheckAuthenticationCode]
parseJSON :: Value -> Parser CheckAuthenticationCode
$cparseJSON :: Value -> Parser CheckAuthenticationCode
toEncodingList :: [RequestQrCodeAuthentication] -> Encoding
$ctoEncodingList :: [RequestQrCodeAuthentication] -> Encoding
toJSONList :: [RequestQrCodeAuthentication] -> Value
$ctoJSONList :: [RequestQrCodeAuthentication] -> Value
toEncoding :: RequestQrCodeAuthentication -> Encoding
$ctoEncoding :: RequestQrCodeAuthentication -> Encoding
toJSON :: RequestQrCodeAuthentication -> Value
$ctoJSON :: RequestQrCodeAuthentication -> Value
parseJSONList :: Value -> Parser [RequestQrCodeAuthentication]
$cparseJSONList :: Value -> Parser [RequestQrCodeAuthentication]
parseJSON :: Value -> Parser RequestQrCodeAuthentication
$cparseJSON :: Value -> Parser RequestQrCodeAuthentication
toEncodingList :: [RegisterUser] -> Encoding
$ctoEncodingList :: [RegisterUser] -> Encoding
toJSONList :: [RegisterUser] -> Value
$ctoJSONList :: [RegisterUser] -> Value
toEncoding :: RegisterUser -> Encoding
$ctoEncoding :: RegisterUser -> Encoding
toJSON :: RegisterUser -> Value
$ctoJSON :: RegisterUser -> Value
parseJSONList :: Value -> Parser [RegisterUser]
$cparseJSONList :: Value -> Parser [RegisterUser]
parseJSON :: Value -> Parser RegisterUser
$cparseJSON :: Value -> Parser RegisterUser
toEncodingList :: [CheckAuthenticationPassword] -> Encoding
$ctoEncodingList :: [CheckAuthenticationPassword] -> Encoding
toJSONList :: [CheckAuthenticationPassword] -> Value
$ctoJSONList :: [CheckAuthenticationPassword] -> Value
toEncoding :: CheckAuthenticationPassword -> Encoding
$ctoEncoding :: CheckAuthenticationPassword -> Encoding
toJSON :: CheckAuthenticationPassword -> Value
$ctoJSON :: CheckAuthenticationPassword -> Value
parseJSONList :: Value -> Parser [CheckAuthenticationPassword]
$cparseJSONList :: Value -> Parser [CheckAuthenticationPassword]
parseJSON :: Value -> Parser CheckAuthenticationPassword
$cparseJSON :: Value -> Parser CheckAuthenticationPassword
toEncodingList :: [RequestAuthenticationPasswordRecovery] -> Encoding
$ctoEncodingList :: [RequestAuthenticationPasswordRecovery] -> Encoding
toJSONList :: [RequestAuthenticationPasswordRecovery] -> Value
$ctoJSONList :: [RequestAuthenticationPasswordRecovery] -> Value
toEncoding :: RequestAuthenticationPasswordRecovery -> Encoding
$ctoEncoding :: RequestAuthenticationPasswordRecovery -> Encoding
toJSON :: RequestAuthenticationPasswordRecovery -> Value
$ctoJSON :: RequestAuthenticationPasswordRecovery -> Value
parseJSONList :: Value -> Parser [RequestAuthenticationPasswordRecovery]
$cparseJSONList :: Value -> Parser [RequestAuthenticationPasswordRecovery]
parseJSON :: Value -> Parser RequestAuthenticationPasswordRecovery
$cparseJSON :: Value -> Parser RequestAuthenticationPasswordRecovery
toEncodingList :: [RecoverAuthenticationPassword] -> Encoding
$ctoEncodingList :: [RecoverAuthenticationPassword] -> Encoding
toJSONList :: [RecoverAuthenticationPassword] -> Value
$ctoJSONList :: [RecoverAuthenticationPassword] -> Value
toEncoding :: RecoverAuthenticationPassword -> Encoding
$ctoEncoding :: RecoverAuthenticationPassword -> Encoding
toJSON :: RecoverAuthenticationPassword -> Value
$ctoJSON :: RecoverAuthenticationPassword -> Value
parseJSONList :: Value -> Parser [RecoverAuthenticationPassword]
$cparseJSONList :: Value -> Parser [RecoverAuthenticationPassword]
parseJSON :: Value -> Parser RecoverAuthenticationPassword
$cparseJSON :: Value -> Parser RecoverAuthenticationPassword
toEncodingList :: [CheckAuthenticationBotToken] -> Encoding
$ctoEncodingList :: [CheckAuthenticationBotToken] -> Encoding
toJSONList :: [CheckAuthenticationBotToken] -> Value
$ctoJSONList :: [CheckAuthenticationBotToken] -> Value
toEncoding :: CheckAuthenticationBotToken -> Encoding
$ctoEncoding :: CheckAuthenticationBotToken -> Encoding
toJSON :: CheckAuthenticationBotToken -> Value
$ctoJSON :: CheckAuthenticationBotToken -> Value
parseJSONList :: Value -> Parser [CheckAuthenticationBotToken]
$cparseJSONList :: Value -> Parser [CheckAuthenticationBotToken]
parseJSON :: Value -> Parser CheckAuthenticationBotToken
$cparseJSON :: Value -> Parser CheckAuthenticationBotToken
toEncodingList :: [LogOut] -> Encoding
$ctoEncodingList :: [LogOut] -> Encoding
toJSONList :: [LogOut] -> Value
$ctoJSONList :: [LogOut] -> Value
toEncoding :: LogOut -> Encoding
$ctoEncoding :: LogOut -> Encoding
toJSON :: LogOut -> Value
$ctoJSON :: LogOut -> Value
parseJSONList :: Value -> Parser [LogOut]
$cparseJSONList :: Value -> Parser [LogOut]
parseJSON :: Value -> Parser LogOut
$cparseJSON :: Value -> Parser LogOut
toEncodingList :: [Close] -> Encoding
$ctoEncodingList :: [Close] -> Encoding
toJSONList :: [Close] -> Value
$ctoJSONList :: [Close] -> Value
toEncoding :: Close -> Encoding
$ctoEncoding :: Close -> Encoding
toJSON :: Close -> Value
$ctoJSON :: Close -> Value
parseJSONList :: Value -> Parser [Close]
$cparseJSONList :: Value -> Parser [Close]
parseJSON :: Value -> Parser Close
$cparseJSON :: Value -> Parser Close
toEncodingList :: [Destroy] -> Encoding
$ctoEncodingList :: [Destroy] -> Encoding
toJSONList :: [Destroy] -> Value
$ctoJSONList :: [Destroy] -> Value
toEncoding :: Destroy -> Encoding
$ctoEncoding :: Destroy -> Encoding
toJSON :: Destroy -> Value
$ctoJSON :: Destroy -> Value
parseJSONList :: Value -> Parser [Destroy]
$cparseJSONList :: Value -> Parser [Destroy]
parseJSON :: Value -> Parser Destroy
$cparseJSON :: Value -> Parser Destroy
toEncodingList :: [ConfirmQrCodeAuthentication] -> Encoding
$ctoEncodingList :: [ConfirmQrCodeAuthentication] -> Encoding
toJSONList :: [ConfirmQrCodeAuthentication] -> Value
$ctoJSONList :: [ConfirmQrCodeAuthentication] -> Value
toEncoding :: ConfirmQrCodeAuthentication -> Encoding
$ctoEncoding :: ConfirmQrCodeAuthentication -> Encoding
toJSON :: ConfirmQrCodeAuthentication -> Value
$ctoJSON :: ConfirmQrCodeAuthentication -> Value
parseJSONList :: Value -> Parser [ConfirmQrCodeAuthentication]
$cparseJSONList :: Value -> Parser [ConfirmQrCodeAuthentication]
parseJSON :: Value -> Parser ConfirmQrCodeAuthentication
$cparseJSON :: Value -> Parser ConfirmQrCodeAuthentication
toEncodingList :: [GetCurrentState] -> Encoding
$ctoEncodingList :: [GetCurrentState] -> Encoding
toJSONList :: [GetCurrentState] -> Value
$ctoJSONList :: [GetCurrentState] -> Value
toEncoding :: GetCurrentState -> Encoding
$ctoEncoding :: GetCurrentState -> Encoding
toJSON :: GetCurrentState -> Value
$ctoJSON :: GetCurrentState -> Value
parseJSONList :: Value -> Parser [GetCurrentState]
$cparseJSONList :: Value -> Parser [GetCurrentState]
parseJSON :: Value -> Parser GetCurrentState
$cparseJSON :: Value -> Parser GetCurrentState
toEncodingList :: [SetDatabaseEncryptionKey] -> Encoding
$ctoEncodingList :: [SetDatabaseEncryptionKey] -> Encoding
toJSONList :: [SetDatabaseEncryptionKey] -> Value
$ctoJSONList :: [SetDatabaseEncryptionKey] -> Value
toEncoding :: SetDatabaseEncryptionKey -> Encoding
$ctoEncoding :: SetDatabaseEncryptionKey -> Encoding
toJSON :: SetDatabaseEncryptionKey -> Value
$ctoJSON :: SetDatabaseEncryptionKey -> Value
parseJSONList :: Value -> Parser [SetDatabaseEncryptionKey]
$cparseJSONList :: Value -> Parser [SetDatabaseEncryptionKey]
parseJSON :: Value -> Parser SetDatabaseEncryptionKey
$cparseJSON :: Value -> Parser SetDatabaseEncryptionKey
toEncodingList :: [GetPasswordState] -> Encoding
$ctoEncodingList :: [GetPasswordState] -> Encoding
toJSONList :: [GetPasswordState] -> Value
$ctoJSONList :: [GetPasswordState] -> Value
toEncoding :: GetPasswordState -> Encoding
$ctoEncoding :: GetPasswordState -> Encoding
toJSON :: GetPasswordState -> Value
$ctoJSON :: GetPasswordState -> Value
parseJSONList :: Value -> Parser [GetPasswordState]
$cparseJSONList :: Value -> Parser [GetPasswordState]
parseJSON :: Value -> Parser GetPasswordState
$cparseJSON :: Value -> Parser GetPasswordState
toEncodingList :: [SetPassword] -> Encoding
$ctoEncodingList :: [SetPassword] -> Encoding
toJSONList :: [SetPassword] -> Value
$ctoJSONList :: [SetPassword] -> Value
toEncoding :: SetPassword -> Encoding
$ctoEncoding :: SetPassword -> Encoding
toJSON :: SetPassword -> Value
$ctoJSON :: SetPassword -> Value
parseJSONList :: Value -> Parser [SetPassword]
$cparseJSONList :: Value -> Parser [SetPassword]
parseJSON :: Value -> Parser SetPassword
$cparseJSON :: Value -> Parser SetPassword
toEncodingList :: [GetRecoveryEmailAddress] -> Encoding
$ctoEncodingList :: [GetRecoveryEmailAddress] -> Encoding
toJSONList :: [GetRecoveryEmailAddress] -> Value
$ctoJSONList :: [GetRecoveryEmailAddress] -> Value
toEncoding :: GetRecoveryEmailAddress -> Encoding
$ctoEncoding :: GetRecoveryEmailAddress -> Encoding
toJSON :: GetRecoveryEmailAddress -> Value
$ctoJSON :: GetRecoveryEmailAddress -> Value
parseJSONList :: Value -> Parser [GetRecoveryEmailAddress]
$cparseJSONList :: Value -> Parser [GetRecoveryEmailAddress]
parseJSON :: Value -> Parser GetRecoveryEmailAddress
$cparseJSON :: Value -> Parser GetRecoveryEmailAddress
toEncodingList :: [SetRecoveryEmailAddress] -> Encoding
$ctoEncodingList :: [SetRecoveryEmailAddress] -> Encoding
toJSONList :: [SetRecoveryEmailAddress] -> Value
$ctoJSONList :: [SetRecoveryEmailAddress] -> Value
toEncoding :: SetRecoveryEmailAddress -> Encoding
$ctoEncoding :: SetRecoveryEmailAddress -> Encoding
toJSON :: SetRecoveryEmailAddress -> Value
$ctoJSON :: SetRecoveryEmailAddress -> Value
parseJSONList :: Value -> Parser [SetRecoveryEmailAddress]
$cparseJSONList :: Value -> Parser [SetRecoveryEmailAddress]
parseJSON :: Value -> Parser SetRecoveryEmailAddress
$cparseJSON :: Value -> Parser SetRecoveryEmailAddress
toEncodingList :: [CheckRecoveryEmailAddressCode] -> Encoding
$ctoEncodingList :: [CheckRecoveryEmailAddressCode] -> Encoding
toJSONList :: [CheckRecoveryEmailAddressCode] -> Value
$ctoJSONList :: [CheckRecoveryEmailAddressCode] -> Value
toEncoding :: CheckRecoveryEmailAddressCode -> Encoding
$ctoEncoding :: CheckRecoveryEmailAddressCode -> Encoding
toJSON :: CheckRecoveryEmailAddressCode -> Value
$ctoJSON :: CheckRecoveryEmailAddressCode -> Value
parseJSONList :: Value -> Parser [CheckRecoveryEmailAddressCode]
$cparseJSONList :: Value -> Parser [CheckRecoveryEmailAddressCode]
parseJSON :: Value -> Parser CheckRecoveryEmailAddressCode
$cparseJSON :: Value -> Parser CheckRecoveryEmailAddressCode
toEncodingList :: [ResendRecoveryEmailAddressCode] -> Encoding
$ctoEncodingList :: [ResendRecoveryEmailAddressCode] -> Encoding
toJSONList :: [ResendRecoveryEmailAddressCode] -> Value
$ctoJSONList :: [ResendRecoveryEmailAddressCode] -> Value
toEncoding :: ResendRecoveryEmailAddressCode -> Encoding
$ctoEncoding :: ResendRecoveryEmailAddressCode -> Encoding
toJSON :: ResendRecoveryEmailAddressCode -> Value
$ctoJSON :: ResendRecoveryEmailAddressCode -> Value
parseJSONList :: Value -> Parser [ResendRecoveryEmailAddressCode]
$cparseJSONList :: Value -> Parser [ResendRecoveryEmailAddressCode]
parseJSON :: Value -> Parser ResendRecoveryEmailAddressCode
$cparseJSON :: Value -> Parser ResendRecoveryEmailAddressCode
toEncodingList :: [RequestPasswordRecovery] -> Encoding
$ctoEncodingList :: [RequestPasswordRecovery] -> Encoding
toJSONList :: [RequestPasswordRecovery] -> Value
$ctoJSONList :: [RequestPasswordRecovery] -> Value
toEncoding :: RequestPasswordRecovery -> Encoding
$ctoEncoding :: RequestPasswordRecovery -> Encoding
toJSON :: RequestPasswordRecovery -> Value
$ctoJSON :: RequestPasswordRecovery -> Value
parseJSONList :: Value -> Parser [RequestPasswordRecovery]
$cparseJSONList :: Value -> Parser [RequestPasswordRecovery]
parseJSON :: Value -> Parser RequestPasswordRecovery
$cparseJSON :: Value -> Parser RequestPasswordRecovery
toEncodingList :: [RecoverPassword] -> Encoding
$ctoEncodingList :: [RecoverPassword] -> Encoding
toJSONList :: [RecoverPassword] -> Value
$ctoJSONList :: [RecoverPassword] -> Value
toEncoding :: RecoverPassword -> Encoding
$ctoEncoding :: RecoverPassword -> Encoding
toJSON :: RecoverPassword -> Value
$ctoJSON :: RecoverPassword -> Value
parseJSONList :: Value -> Parser [RecoverPassword]
$cparseJSONList :: Value -> Parser [RecoverPassword]
parseJSON :: Value -> Parser RecoverPassword
$cparseJSON :: Value -> Parser RecoverPassword
toEncodingList :: [CreateTemporaryPassword] -> Encoding
$ctoEncodingList :: [CreateTemporaryPassword] -> Encoding
toJSONList :: [CreateTemporaryPassword] -> Value
$ctoJSONList :: [CreateTemporaryPassword] -> Value
toEncoding :: CreateTemporaryPassword -> Encoding
$ctoEncoding :: CreateTemporaryPassword -> Encoding
toJSON :: CreateTemporaryPassword -> Value
$ctoJSON :: CreateTemporaryPassword -> Value
parseJSONList :: Value -> Parser [CreateTemporaryPassword]
$cparseJSONList :: Value -> Parser [CreateTemporaryPassword]
parseJSON :: Value -> Parser CreateTemporaryPassword
$cparseJSON :: Value -> Parser CreateTemporaryPassword
toEncodingList :: [GetTemporaryPasswordState] -> Encoding
$ctoEncodingList :: [GetTemporaryPasswordState] -> Encoding
toJSONList :: [GetTemporaryPasswordState] -> Value
$ctoJSONList :: [GetTemporaryPasswordState] -> Value
toEncoding :: GetTemporaryPasswordState -> Encoding
$ctoEncoding :: GetTemporaryPasswordState -> Encoding
toJSON :: GetTemporaryPasswordState -> Value
$ctoJSON :: GetTemporaryPasswordState -> Value
parseJSONList :: Value -> Parser [GetTemporaryPasswordState]
$cparseJSONList :: Value -> Parser [GetTemporaryPasswordState]
parseJSON :: Value -> Parser GetTemporaryPasswordState
$cparseJSON :: Value -> Parser GetTemporaryPasswordState
toEncodingList :: [GetMe] -> Encoding
$ctoEncodingList :: [GetMe] -> Encoding
toJSONList :: [GetMe] -> Value
$ctoJSONList :: [GetMe] -> Value
toEncoding :: GetMe -> Encoding
$ctoEncoding :: GetMe -> Encoding
toJSON :: GetMe -> Value
$ctoJSON :: GetMe -> Value
parseJSONList :: Value -> Parser [GetMe]
$cparseJSONList :: Value -> Parser [GetMe]
parseJSON :: Value -> Parser GetMe
$cparseJSON :: Value -> Parser GetMe
toEncodingList :: [GetUser] -> Encoding
$ctoEncodingList :: [GetUser] -> Encoding
toJSONList :: [GetUser] -> Value
$ctoJSONList :: [GetUser] -> Value
toEncoding :: GetUser -> Encoding
$ctoEncoding :: GetUser -> Encoding
toJSON :: GetUser -> Value
$ctoJSON :: GetUser -> Value
parseJSONList :: Value -> Parser [GetUser]
$cparseJSONList :: Value -> Parser [GetUser]
parseJSON :: Value -> Parser GetUser
$cparseJSON :: Value -> Parser GetUser
toEncodingList :: [GetUserFullInfo] -> Encoding
$ctoEncodingList :: [GetUserFullInfo] -> Encoding
toJSONList :: [GetUserFullInfo] -> Value
$ctoJSONList :: [GetUserFullInfo] -> Value
toEncoding :: GetUserFullInfo -> Encoding
$ctoEncoding :: GetUserFullInfo -> Encoding
toJSON :: GetUserFullInfo -> Value
$ctoJSON :: GetUserFullInfo -> Value
parseJSONList :: Value -> Parser [GetUserFullInfo]
$cparseJSONList :: Value -> Parser [GetUserFullInfo]
parseJSON :: Value -> Parser GetUserFullInfo
$cparseJSON :: Value -> Parser GetUserFullInfo
toEncodingList :: [GetBasicGroup] -> Encoding
$ctoEncodingList :: [GetBasicGroup] -> Encoding
toJSONList :: [GetBasicGroup] -> Value
$ctoJSONList :: [GetBasicGroup] -> Value
toEncoding :: GetBasicGroup -> Encoding
$ctoEncoding :: GetBasicGroup -> Encoding
toJSON :: GetBasicGroup -> Value
$ctoJSON :: GetBasicGroup -> Value
parseJSONList :: Value -> Parser [GetBasicGroup]
$cparseJSONList :: Value -> Parser [GetBasicGroup]
parseJSON :: Value -> Parser GetBasicGroup
$cparseJSON :: Value -> Parser GetBasicGroup
toEncodingList :: [GetBasicGroupFullInfo] -> Encoding
$ctoEncodingList :: [GetBasicGroupFullInfo] -> Encoding
toJSONList :: [GetBasicGroupFullInfo] -> Value
$ctoJSONList :: [GetBasicGroupFullInfo] -> Value
toEncoding :: GetBasicGroupFullInfo -> Encoding
$ctoEncoding :: GetBasicGroupFullInfo -> Encoding
toJSON :: GetBasicGroupFullInfo -> Value
$ctoJSON :: GetBasicGroupFullInfo -> Value
parseJSONList :: Value -> Parser [GetBasicGroupFullInfo]
$cparseJSONList :: Value -> Parser [GetBasicGroupFullInfo]
parseJSON :: Value -> Parser GetBasicGroupFullInfo
$cparseJSON :: Value -> Parser GetBasicGroupFullInfo
toEncodingList :: [GetSupergroup] -> Encoding
$ctoEncodingList :: [GetSupergroup] -> Encoding
toJSONList :: [GetSupergroup] -> Value
$ctoJSONList :: [GetSupergroup] -> Value
toEncoding :: GetSupergroup -> Encoding
$ctoEncoding :: GetSupergroup -> Encoding
toJSON :: GetSupergroup -> Value
$ctoJSON :: GetSupergroup -> Value
parseJSONList :: Value -> Parser [GetSupergroup]
$cparseJSONList :: Value -> Parser [GetSupergroup]
parseJSON :: Value -> Parser GetSupergroup
$cparseJSON :: Value -> Parser GetSupergroup
toEncodingList :: [GetSupergroupFullInfo] -> Encoding
$ctoEncodingList :: [GetSupergroupFullInfo] -> Encoding
toJSONList :: [GetSupergroupFullInfo] -> Value
$ctoJSONList :: [GetSupergroupFullInfo] -> Value
toEncoding :: GetSupergroupFullInfo -> Encoding
$ctoEncoding :: GetSupergroupFullInfo -> Encoding
toJSON :: GetSupergroupFullInfo -> Value
$ctoJSON :: GetSupergroupFullInfo -> Value
parseJSONList :: Value -> Parser [GetSupergroupFullInfo]
$cparseJSONList :: Value -> Parser [GetSupergroupFullInfo]
parseJSON :: Value -> Parser GetSupergroupFullInfo
$cparseJSON :: Value -> Parser GetSupergroupFullInfo
toEncodingList :: [GetSecretChat] -> Encoding
$ctoEncodingList :: [GetSecretChat] -> Encoding
toJSONList :: [GetSecretChat] -> Value
$ctoJSONList :: [GetSecretChat] -> Value
toEncoding :: GetSecretChat -> Encoding
$ctoEncoding :: GetSecretChat -> Encoding
toJSON :: GetSecretChat -> Value
$ctoJSON :: GetSecretChat -> Value
parseJSONList :: Value -> Parser [GetSecretChat]
$cparseJSONList :: Value -> Parser [GetSecretChat]
parseJSON :: Value -> Parser GetSecretChat
$cparseJSON :: Value -> Parser GetSecretChat
toEncodingList :: [GetChat] -> Encoding
$ctoEncodingList :: [GetChat] -> Encoding
toJSONList :: [GetChat] -> Value
$ctoJSONList :: [GetChat] -> Value
toEncoding :: GetChat -> Encoding
$ctoEncoding :: GetChat -> Encoding
toJSON :: GetChat -> Value
$ctoJSON :: GetChat -> Value
parseJSONList :: Value -> Parser [GetChat]
$cparseJSONList :: Value -> Parser [GetChat]
parseJSON :: Value -> Parser GetChat
$cparseJSON :: Value -> Parser GetChat
toEncodingList :: [GetMessage] -> Encoding
$ctoEncodingList :: [GetMessage] -> Encoding
toJSONList :: [GetMessage] -> Value
$ctoJSONList :: [GetMessage] -> Value
toEncoding :: GetMessage -> Encoding
$ctoEncoding :: GetMessage -> Encoding
toJSON :: GetMessage -> Value
$ctoJSON :: GetMessage -> Value
parseJSONList :: Value -> Parser [GetMessage]
$cparseJSONList :: Value -> Parser [GetMessage]
parseJSON :: Value -> Parser GetMessage
$cparseJSON :: Value -> Parser GetMessage
toEncodingList :: [GetMessageLocally] -> Encoding
$ctoEncodingList :: [GetMessageLocally] -> Encoding
toJSONList :: [GetMessageLocally] -> Value
$ctoJSONList :: [GetMessageLocally] -> Value
toEncoding :: GetMessageLocally -> Encoding
$ctoEncoding :: GetMessageLocally -> Encoding
toJSON :: GetMessageLocally -> Value
$ctoJSON :: GetMessageLocally -> Value
parseJSONList :: Value -> Parser [GetMessageLocally]
$cparseJSONList :: Value -> Parser [GetMessageLocally]
parseJSON :: Value -> Parser GetMessageLocally
$cparseJSON :: Value -> Parser GetMessageLocally
toEncodingList :: [GetRepliedMessage] -> Encoding
$ctoEncodingList :: [GetRepliedMessage] -> Encoding
toJSONList :: [GetRepliedMessage] -> Value
$ctoJSONList :: [GetRepliedMessage] -> Value
toEncoding :: GetRepliedMessage -> Encoding
$ctoEncoding :: GetRepliedMessage -> Encoding
toJSON :: GetRepliedMessage -> Value
$ctoJSON :: GetRepliedMessage -> Value
parseJSONList :: Value -> Parser [GetRepliedMessage]
$cparseJSONList :: Value -> Parser [GetRepliedMessage]
parseJSON :: Value -> Parser GetRepliedMessage
$cparseJSON :: Value -> Parser GetRepliedMessage
toEncodingList :: [GetChatPinnedMessage] -> Encoding
$ctoEncodingList :: [GetChatPinnedMessage] -> Encoding
toJSONList :: [GetChatPinnedMessage] -> Value
$ctoJSONList :: [GetChatPinnedMessage] -> Value
toEncoding :: GetChatPinnedMessage -> Encoding
$ctoEncoding :: GetChatPinnedMessage -> Encoding
toJSON :: GetChatPinnedMessage -> Value
$ctoJSON :: GetChatPinnedMessage -> Value
parseJSONList :: Value -> Parser [GetChatPinnedMessage]
$cparseJSONList :: Value -> Parser [GetChatPinnedMessage]
parseJSON :: Value -> Parser GetChatPinnedMessage
$cparseJSON :: Value -> Parser GetChatPinnedMessage
toEncodingList :: [GetMessages] -> Encoding
$ctoEncodingList :: [GetMessages] -> Encoding
toJSONList :: [GetMessages] -> Value
$ctoJSONList :: [GetMessages] -> Value
toEncoding :: GetMessages -> Encoding
$ctoEncoding :: GetMessages -> Encoding
toJSON :: GetMessages -> Value
$ctoJSON :: GetMessages -> Value
parseJSONList :: Value -> Parser [GetMessages]
$cparseJSONList :: Value -> Parser [GetMessages]
parseJSON :: Value -> Parser GetMessages
$cparseJSON :: Value -> Parser GetMessages
toEncodingList :: [GetFile] -> Encoding
$ctoEncodingList :: [GetFile] -> Encoding
toJSONList :: [GetFile] -> Value
$ctoJSONList :: [GetFile] -> Value
toEncoding :: GetFile -> Encoding
$ctoEncoding :: GetFile -> Encoding
toJSON :: GetFile -> Value
$ctoJSON :: GetFile -> Value
parseJSONList :: Value -> Parser [GetFile]
$cparseJSONList :: Value -> Parser [GetFile]
parseJSON :: Value -> Parser GetFile
$cparseJSON :: Value -> Parser GetFile
toEncodingList :: [GetRemoteFile] -> Encoding
$ctoEncodingList :: [GetRemoteFile] -> Encoding
toJSONList :: [GetRemoteFile] -> Value
$ctoJSONList :: [GetRemoteFile] -> Value
toEncoding :: GetRemoteFile -> Encoding
$ctoEncoding :: GetRemoteFile -> Encoding
toJSON :: GetRemoteFile -> Value
$ctoJSON :: GetRemoteFile -> Value
parseJSONList :: Value -> Parser [GetRemoteFile]
$cparseJSONList :: Value -> Parser [GetRemoteFile]
parseJSON :: Value -> Parser GetRemoteFile
$cparseJSON :: Value -> Parser GetRemoteFile
toEncodingList :: [GetChats] -> Encoding
$ctoEncodingList :: [GetChats] -> Encoding
toJSONList :: [GetChats] -> Value
$ctoJSONList :: [GetChats] -> Value
toEncoding :: GetChats -> Encoding
$ctoEncoding :: GetChats -> Encoding
toJSON :: GetChats -> Value
$ctoJSON :: GetChats -> Value
parseJSONList :: Value -> Parser [GetChats]
$cparseJSONList :: Value -> Parser [GetChats]
parseJSON :: Value -> Parser GetChats
$cparseJSON :: Value -> Parser GetChats
toEncodingList :: [SearchPublicChat] -> Encoding
$ctoEncodingList :: [SearchPublicChat] -> Encoding
toJSONList :: [SearchPublicChat] -> Value
$ctoJSONList :: [SearchPublicChat] -> Value
toEncoding :: SearchPublicChat -> Encoding
$ctoEncoding :: SearchPublicChat -> Encoding
toJSON :: SearchPublicChat -> Value
$ctoJSON :: SearchPublicChat -> Value
parseJSONList :: Value -> Parser [SearchPublicChat]
$cparseJSONList :: Value -> Parser [SearchPublicChat]
parseJSON :: Value -> Parser SearchPublicChat
$cparseJSON :: Value -> Parser SearchPublicChat
toEncodingList :: [SearchPublicChats] -> Encoding
$ctoEncodingList :: [SearchPublicChats] -> Encoding
toJSONList :: [SearchPublicChats] -> Value
$ctoJSONList :: [SearchPublicChats] -> Value
toEncoding :: SearchPublicChats -> Encoding
$ctoEncoding :: SearchPublicChats -> Encoding
toJSON :: SearchPublicChats -> Value
$ctoJSON :: SearchPublicChats -> Value
parseJSONList :: Value -> Parser [SearchPublicChats]
$cparseJSONList :: Value -> Parser [SearchPublicChats]
parseJSON :: Value -> Parser SearchPublicChats
$cparseJSON :: Value -> Parser SearchPublicChats
toEncodingList :: [SearchChats] -> Encoding
$ctoEncodingList :: [SearchChats] -> Encoding
toJSONList :: [SearchChats] -> Value
$ctoJSONList :: [SearchChats] -> Value
toEncoding :: SearchChats -> Encoding
$ctoEncoding :: SearchChats -> Encoding
toJSON :: SearchChats -> Value
$ctoJSON :: SearchChats -> Value
parseJSONList :: Value -> Parser [SearchChats]
$cparseJSONList :: Value -> Parser [SearchChats]
parseJSON :: Value -> Parser SearchChats
$cparseJSON :: Value -> Parser SearchChats
toEncodingList :: [SearchChatsOnServer] -> Encoding
$ctoEncodingList :: [SearchChatsOnServer] -> Encoding
toJSONList :: [SearchChatsOnServer] -> Value
$ctoJSONList :: [SearchChatsOnServer] -> Value
toEncoding :: SearchChatsOnServer -> Encoding
$ctoEncoding :: SearchChatsOnServer -> Encoding
toJSON :: SearchChatsOnServer -> Value
$ctoJSON :: SearchChatsOnServer -> Value
parseJSONList :: Value -> Parser [SearchChatsOnServer]
$cparseJSONList :: Value -> Parser [SearchChatsOnServer]
parseJSON :: Value -> Parser SearchChatsOnServer
$cparseJSON :: Value -> Parser SearchChatsOnServer
toEncodingList :: [SearchChatsNearby] -> Encoding
$ctoEncodingList :: [SearchChatsNearby] -> Encoding
toJSONList :: [SearchChatsNearby] -> Value
$ctoJSONList :: [SearchChatsNearby] -> Value
toEncoding :: SearchChatsNearby -> Encoding
$ctoEncoding :: SearchChatsNearby -> Encoding
toJSON :: SearchChatsNearby -> Value
$ctoJSON :: SearchChatsNearby -> Value
parseJSONList :: Value -> Parser [SearchChatsNearby]
$cparseJSONList :: Value -> Parser [SearchChatsNearby]
parseJSON :: Value -> Parser SearchChatsNearby
$cparseJSON :: Value -> Parser SearchChatsNearby
toEncodingList :: [GetTopChats] -> Encoding
$ctoEncodingList :: [GetTopChats] -> Encoding
toJSONList :: [GetTopChats] -> Value
$ctoJSONList :: [GetTopChats] -> Value
toEncoding :: GetTopChats -> Encoding
$ctoEncoding :: GetTopChats -> Encoding
toJSON :: GetTopChats -> Value
$ctoJSON :: GetTopChats -> Value
parseJSONList :: Value -> Parser [GetTopChats]
$cparseJSONList :: Value -> Parser [GetTopChats]
parseJSON :: Value -> Parser GetTopChats
$cparseJSON :: Value -> Parser GetTopChats
toEncodingList :: [RemoveTopChat] -> Encoding
$ctoEncodingList :: [RemoveTopChat] -> Encoding
toJSONList :: [RemoveTopChat] -> Value
$ctoJSONList :: [RemoveTopChat] -> Value
toEncoding :: RemoveTopChat -> Encoding
$ctoEncoding :: RemoveTopChat -> Encoding
toJSON :: RemoveTopChat -> Value
$ctoJSON :: RemoveTopChat -> Value
parseJSONList :: Value -> Parser [RemoveTopChat]
$cparseJSONList :: Value -> Parser [RemoveTopChat]
parseJSON :: Value -> Parser RemoveTopChat
$cparseJSON :: Value -> Parser RemoveTopChat
toEncodingList :: [AddRecentlyFoundChat] -> Encoding
$ctoEncodingList :: [AddRecentlyFoundChat] -> Encoding
toJSONList :: [AddRecentlyFoundChat] -> Value
$ctoJSONList :: [AddRecentlyFoundChat] -> Value
toEncoding :: AddRecentlyFoundChat -> Encoding
$ctoEncoding :: AddRecentlyFoundChat -> Encoding
toJSON :: AddRecentlyFoundChat -> Value
$ctoJSON :: AddRecentlyFoundChat -> Value
parseJSONList :: Value -> Parser [AddRecentlyFoundChat]
$cparseJSONList :: Value -> Parser [AddRecentlyFoundChat]
parseJSON :: Value -> Parser AddRecentlyFoundChat
$cparseJSON :: Value -> Parser AddRecentlyFoundChat
toEncodingList :: [RemoveRecentlyFoundChat] -> Encoding
$ctoEncodingList :: [RemoveRecentlyFoundChat] -> Encoding
toJSONList :: [RemoveRecentlyFoundChat] -> Value
$ctoJSONList :: [RemoveRecentlyFoundChat] -> Value
toEncoding :: RemoveRecentlyFoundChat -> Encoding
$ctoEncoding :: RemoveRecentlyFoundChat -> Encoding
toJSON :: RemoveRecentlyFoundChat -> Value
$ctoJSON :: RemoveRecentlyFoundChat -> Value
parseJSONList :: Value -> Parser [RemoveRecentlyFoundChat]
$cparseJSONList :: Value -> Parser [RemoveRecentlyFoundChat]
parseJSON :: Value -> Parser RemoveRecentlyFoundChat
$cparseJSON :: Value -> Parser RemoveRecentlyFoundChat
toEncodingList :: [ClearRecentlyFoundChats] -> Encoding
$ctoEncodingList :: [ClearRecentlyFoundChats] -> Encoding
toJSONList :: [ClearRecentlyFoundChats] -> Value
$ctoJSONList :: [ClearRecentlyFoundChats] -> Value
toEncoding :: ClearRecentlyFoundChats -> Encoding
$ctoEncoding :: ClearRecentlyFoundChats -> Encoding
toJSON :: ClearRecentlyFoundChats -> Value
$ctoJSON :: ClearRecentlyFoundChats -> Value
parseJSONList :: Value -> Parser [ClearRecentlyFoundChats]
$cparseJSONList :: Value -> Parser [ClearRecentlyFoundChats]
parseJSON :: Value -> Parser ClearRecentlyFoundChats
$cparseJSON :: Value -> Parser ClearRecentlyFoundChats
toEncodingList :: [CheckChatUsername] -> Encoding
$ctoEncodingList :: [CheckChatUsername] -> Encoding
toJSONList :: [CheckChatUsername] -> Value
$ctoJSONList :: [CheckChatUsername] -> Value
toEncoding :: CheckChatUsername -> Encoding
$ctoEncoding :: CheckChatUsername -> Encoding
toJSON :: CheckChatUsername -> Value
$ctoJSON :: CheckChatUsername -> Value
parseJSONList :: Value -> Parser [CheckChatUsername]
$cparseJSONList :: Value -> Parser [CheckChatUsername]
parseJSON :: Value -> Parser CheckChatUsername
$cparseJSON :: Value -> Parser CheckChatUsername
toEncodingList :: [GetCreatedPublicChats] -> Encoding
$ctoEncodingList :: [GetCreatedPublicChats] -> Encoding
toJSONList :: [GetCreatedPublicChats] -> Value
$ctoJSONList :: [GetCreatedPublicChats] -> Value
toEncoding :: GetCreatedPublicChats -> Encoding
$ctoEncoding :: GetCreatedPublicChats -> Encoding
toJSON :: GetCreatedPublicChats -> Value
$ctoJSON :: GetCreatedPublicChats -> Value
parseJSONList :: Value -> Parser [GetCreatedPublicChats]
$cparseJSONList :: Value -> Parser [GetCreatedPublicChats]
parseJSON :: Value -> Parser GetCreatedPublicChats
$cparseJSON :: Value -> Parser GetCreatedPublicChats
toEncodingList :: [CheckCreatedPublicChatsLimit] -> Encoding
$ctoEncodingList :: [CheckCreatedPublicChatsLimit] -> Encoding
toJSONList :: [CheckCreatedPublicChatsLimit] -> Value
$ctoJSONList :: [CheckCreatedPublicChatsLimit] -> Value
toEncoding :: CheckCreatedPublicChatsLimit -> Encoding
$ctoEncoding :: CheckCreatedPublicChatsLimit -> Encoding
toJSON :: CheckCreatedPublicChatsLimit -> Value
$ctoJSON :: CheckCreatedPublicChatsLimit -> Value
parseJSONList :: Value -> Parser [CheckCreatedPublicChatsLimit]
$cparseJSONList :: Value -> Parser [CheckCreatedPublicChatsLimit]
parseJSON :: Value -> Parser CheckCreatedPublicChatsLimit
$cparseJSON :: Value -> Parser CheckCreatedPublicChatsLimit
toEncodingList :: [GetSuitableDiscussionChats] -> Encoding
$ctoEncodingList :: [GetSuitableDiscussionChats] -> Encoding
toJSONList :: [GetSuitableDiscussionChats] -> Value
$ctoJSONList :: [GetSuitableDiscussionChats] -> Value
toEncoding :: GetSuitableDiscussionChats -> Encoding
$ctoEncoding :: GetSuitableDiscussionChats -> Encoding
toJSON :: GetSuitableDiscussionChats -> Value
$ctoJSON :: GetSuitableDiscussionChats -> Value
parseJSONList :: Value -> Parser [GetSuitableDiscussionChats]
$cparseJSONList :: Value -> Parser [GetSuitableDiscussionChats]
parseJSON :: Value -> Parser GetSuitableDiscussionChats
$cparseJSON :: Value -> Parser GetSuitableDiscussionChats
toEncodingList :: [GetInactiveSupergroupChats] -> Encoding
$ctoEncodingList :: [GetInactiveSupergroupChats] -> Encoding
toJSONList :: [GetInactiveSupergroupChats] -> Value
$ctoJSONList :: [GetInactiveSupergroupChats] -> Value
toEncoding :: GetInactiveSupergroupChats -> Encoding
$ctoEncoding :: GetInactiveSupergroupChats -> Encoding
toJSON :: GetInactiveSupergroupChats -> Value
$ctoJSON :: GetInactiveSupergroupChats -> Value
parseJSONList :: Value -> Parser [GetInactiveSupergroupChats]
$cparseJSONList :: Value -> Parser [GetInactiveSupergroupChats]
parseJSON :: Value -> Parser GetInactiveSupergroupChats
$cparseJSON :: Value -> Parser GetInactiveSupergroupChats
toEncodingList :: [GetGroupsInCommon] -> Encoding
$ctoEncodingList :: [GetGroupsInCommon] -> Encoding
toJSONList :: [GetGroupsInCommon] -> Value
$ctoJSONList :: [GetGroupsInCommon] -> Value
toEncoding :: GetGroupsInCommon -> Encoding
$ctoEncoding :: GetGroupsInCommon -> Encoding
toJSON :: GetGroupsInCommon -> Value
$ctoJSON :: GetGroupsInCommon -> Value
parseJSONList :: Value -> Parser [GetGroupsInCommon]
$cparseJSONList :: Value -> Parser [GetGroupsInCommon]
parseJSON :: Value -> Parser GetGroupsInCommon
$cparseJSON :: Value -> Parser GetGroupsInCommon
toEncodingList :: [GetChatHistory] -> Encoding
$ctoEncodingList :: [GetChatHistory] -> Encoding
toJSONList :: [GetChatHistory] -> Value
$ctoJSONList :: [GetChatHistory] -> Value
toEncoding :: GetChatHistory -> Encoding
$ctoEncoding :: GetChatHistory -> Encoding
toJSON :: GetChatHistory -> Value
$ctoJSON :: GetChatHistory -> Value
parseJSONList :: Value -> Parser [GetChatHistory]
$cparseJSONList :: Value -> Parser [GetChatHistory]
parseJSON :: Value -> Parser GetChatHistory
$cparseJSON :: Value -> Parser GetChatHistory
toEncodingList :: [DeleteChatHistory] -> Encoding
$ctoEncodingList :: [DeleteChatHistory] -> Encoding
toJSONList :: [DeleteChatHistory] -> Value
$ctoJSONList :: [DeleteChatHistory] -> Value
toEncoding :: DeleteChatHistory -> Encoding
$ctoEncoding :: DeleteChatHistory -> Encoding
toJSON :: DeleteChatHistory -> Value
$ctoJSON :: DeleteChatHistory -> Value
parseJSONList :: Value -> Parser [DeleteChatHistory]
$cparseJSONList :: Value -> Parser [DeleteChatHistory]
parseJSON :: Value -> Parser DeleteChatHistory
$cparseJSON :: Value -> Parser DeleteChatHistory
toEncodingList :: [SearchChatMessages] -> Encoding
$ctoEncodingList :: [SearchChatMessages] -> Encoding
toJSONList :: [SearchChatMessages] -> Value
$ctoJSONList :: [SearchChatMessages] -> Value
toEncoding :: SearchChatMessages -> Encoding
$ctoEncoding :: SearchChatMessages -> Encoding
toJSON :: SearchChatMessages -> Value
$ctoJSON :: SearchChatMessages -> Value
parseJSONList :: Value -> Parser [SearchChatMessages]
$cparseJSONList :: Value -> Parser [SearchChatMessages]
parseJSON :: Value -> Parser SearchChatMessages
$cparseJSON :: Value -> Parser SearchChatMessages
toEncodingList :: [SearchMessages] -> Encoding
$ctoEncodingList :: [SearchMessages] -> Encoding
toJSONList :: [SearchMessages] -> Value
$ctoJSONList :: [SearchMessages] -> Value
toEncoding :: SearchMessages -> Encoding
$ctoEncoding :: SearchMessages -> Encoding
toJSON :: SearchMessages -> Value
$ctoJSON :: SearchMessages -> Value
parseJSONList :: Value -> Parser [SearchMessages]
$cparseJSONList :: Value -> Parser [SearchMessages]
parseJSON :: Value -> Parser SearchMessages
$cparseJSON :: Value -> Parser SearchMessages
toEncodingList :: [SearchSecretMessages] -> Encoding
$ctoEncodingList :: [SearchSecretMessages] -> Encoding
toJSONList :: [SearchSecretMessages] -> Value
$ctoJSONList :: [SearchSecretMessages] -> Value
toEncoding :: SearchSecretMessages -> Encoding
$ctoEncoding :: SearchSecretMessages -> Encoding
toJSON :: SearchSecretMessages -> Value
$ctoJSON :: SearchSecretMessages -> Value
parseJSONList :: Value -> Parser [SearchSecretMessages]
$cparseJSONList :: Value -> Parser [SearchSecretMessages]
parseJSON :: Value -> Parser SearchSecretMessages
$cparseJSON :: Value -> Parser SearchSecretMessages
toEncodingList :: [SearchCallMessages] -> Encoding
$ctoEncodingList :: [SearchCallMessages] -> Encoding
toJSONList :: [SearchCallMessages] -> Value
$ctoJSONList :: [SearchCallMessages] -> Value
toEncoding :: SearchCallMessages -> Encoding
$ctoEncoding :: SearchCallMessages -> Encoding
toJSON :: SearchCallMessages -> Value
$ctoJSON :: SearchCallMessages -> Value
parseJSONList :: Value -> Parser [SearchCallMessages]
$cparseJSONList :: Value -> Parser [SearchCallMessages]
parseJSON :: Value -> Parser SearchCallMessages
$cparseJSON :: Value -> Parser SearchCallMessages
toEncodingList :: [SearchChatRecentLocationMessages] -> Encoding
$ctoEncodingList :: [SearchChatRecentLocationMessages] -> Encoding
toJSONList :: [SearchChatRecentLocationMessages] -> Value
$ctoJSONList :: [SearchChatRecentLocationMessages] -> Value
toEncoding :: SearchChatRecentLocationMessages -> Encoding
$ctoEncoding :: SearchChatRecentLocationMessages -> Encoding
toJSON :: SearchChatRecentLocationMessages -> Value
$ctoJSON :: SearchChatRecentLocationMessages -> Value
parseJSONList :: Value -> Parser [SearchChatRecentLocationMessages]
$cparseJSONList :: Value -> Parser [SearchChatRecentLocationMessages]
parseJSON :: Value -> Parser SearchChatRecentLocationMessages
$cparseJSON :: Value -> Parser SearchChatRecentLocationMessages
toEncodingList :: [GetActiveLiveLocationMessages] -> Encoding
$ctoEncodingList :: [GetActiveLiveLocationMessages] -> Encoding
toJSONList :: [GetActiveLiveLocationMessages] -> Value
$ctoJSONList :: [GetActiveLiveLocationMessages] -> Value
toEncoding :: GetActiveLiveLocationMessages -> Encoding
$ctoEncoding :: GetActiveLiveLocationMessages -> Encoding
toJSON :: GetActiveLiveLocationMessages -> Value
$ctoJSON :: GetActiveLiveLocationMessages -> Value
parseJSONList :: Value -> Parser [GetActiveLiveLocationMessages]
$cparseJSONList :: Value -> Parser [GetActiveLiveLocationMessages]
parseJSON :: Value -> Parser GetActiveLiveLocationMessages
$cparseJSON :: Value -> Parser GetActiveLiveLocationMessages
toEncodingList :: [GetChatMessageByDate] -> Encoding
$ctoEncodingList :: [GetChatMessageByDate] -> Encoding
toJSONList :: [GetChatMessageByDate] -> Value
$ctoJSONList :: [GetChatMessageByDate] -> Value
toEncoding :: GetChatMessageByDate -> Encoding
$ctoEncoding :: GetChatMessageByDate -> Encoding
toJSON :: GetChatMessageByDate -> Value
$ctoJSON :: GetChatMessageByDate -> Value
parseJSONList :: Value -> Parser [GetChatMessageByDate]
$cparseJSONList :: Value -> Parser [GetChatMessageByDate]
parseJSON :: Value -> Parser GetChatMessageByDate
$cparseJSON :: Value -> Parser GetChatMessageByDate
toEncodingList :: [GetChatMessageCount] -> Encoding
$ctoEncodingList :: [GetChatMessageCount] -> Encoding
toJSONList :: [GetChatMessageCount] -> Value
$ctoJSONList :: [GetChatMessageCount] -> Value
toEncoding :: GetChatMessageCount -> Encoding
$ctoEncoding :: GetChatMessageCount -> Encoding
toJSON :: GetChatMessageCount -> Value
$ctoJSON :: GetChatMessageCount -> Value
parseJSONList :: Value -> Parser [GetChatMessageCount]
$cparseJSONList :: Value -> Parser [GetChatMessageCount]
parseJSON :: Value -> Parser GetChatMessageCount
$cparseJSON :: Value -> Parser GetChatMessageCount
toEncodingList :: [GetChatScheduledMessages] -> Encoding
$ctoEncodingList :: [GetChatScheduledMessages] -> Encoding
toJSONList :: [GetChatScheduledMessages] -> Value
$ctoJSONList :: [GetChatScheduledMessages] -> Value
toEncoding :: GetChatScheduledMessages -> Encoding
$ctoEncoding :: GetChatScheduledMessages -> Encoding
toJSON :: GetChatScheduledMessages -> Value
$ctoJSON :: GetChatScheduledMessages -> Value
parseJSONList :: Value -> Parser [GetChatScheduledMessages]
$cparseJSONList :: Value -> Parser [GetChatScheduledMessages]
parseJSON :: Value -> Parser GetChatScheduledMessages
$cparseJSON :: Value -> Parser GetChatScheduledMessages
toEncodingList :: [RemoveNotification] -> Encoding
$ctoEncodingList :: [RemoveNotification] -> Encoding
toJSONList :: [RemoveNotification] -> Value
$ctoJSONList :: [RemoveNotification] -> Value
toEncoding :: RemoveNotification -> Encoding
$ctoEncoding :: RemoveNotification -> Encoding
toJSON :: RemoveNotification -> Value
$ctoJSON :: RemoveNotification -> Value
parseJSONList :: Value -> Parser [RemoveNotification]
$cparseJSONList :: Value -> Parser [RemoveNotification]
parseJSON :: Value -> Parser RemoveNotification
$cparseJSON :: Value -> Parser RemoveNotification
toEncodingList :: [RemoveNotificationGroup] -> Encoding
$ctoEncodingList :: [RemoveNotificationGroup] -> Encoding
toJSONList :: [RemoveNotificationGroup] -> Value
$ctoJSONList :: [RemoveNotificationGroup] -> Value
toEncoding :: RemoveNotificationGroup -> Encoding
$ctoEncoding :: RemoveNotificationGroup -> Encoding
toJSON :: RemoveNotificationGroup -> Value
$ctoJSON :: RemoveNotificationGroup -> Value
parseJSONList :: Value -> Parser [RemoveNotificationGroup]
$cparseJSONList :: Value -> Parser [RemoveNotificationGroup]
parseJSON :: Value -> Parser RemoveNotificationGroup
$cparseJSON :: Value -> Parser RemoveNotificationGroup
toEncodingList :: [GetPublicMessageLink] -> Encoding
$ctoEncodingList :: [GetPublicMessageLink] -> Encoding
toJSONList :: [GetPublicMessageLink] -> Value
$ctoJSONList :: [GetPublicMessageLink] -> Value
toEncoding :: GetPublicMessageLink -> Encoding
$ctoEncoding :: GetPublicMessageLink -> Encoding
toJSON :: GetPublicMessageLink -> Value
$ctoJSON :: GetPublicMessageLink -> Value
parseJSONList :: Value -> Parser [GetPublicMessageLink]
$cparseJSONList :: Value -> Parser [GetPublicMessageLink]
parseJSON :: Value -> Parser GetPublicMessageLink
$cparseJSON :: Value -> Parser GetPublicMessageLink
toEncodingList :: [GetMessageLink] -> Encoding
$ctoEncodingList :: [GetMessageLink] -> Encoding
toJSONList :: [GetMessageLink] -> Value
$ctoJSONList :: [GetMessageLink] -> Value
toEncoding :: GetMessageLink -> Encoding
$ctoEncoding :: GetMessageLink -> Encoding
toJSON :: GetMessageLink -> Value
$ctoJSON :: GetMessageLink -> Value
parseJSONList :: Value -> Parser [GetMessageLink]
$cparseJSONList :: Value -> Parser [GetMessageLink]
parseJSON :: Value -> Parser GetMessageLink
$cparseJSON :: Value -> Parser GetMessageLink
toEncodingList :: [GetMessageLinkInfo] -> Encoding
$ctoEncodingList :: [GetMessageLinkInfo] -> Encoding
toJSONList :: [GetMessageLinkInfo] -> Value
$ctoJSONList :: [GetMessageLinkInfo] -> Value
toEncoding :: GetMessageLinkInfo -> Encoding
$ctoEncoding :: GetMessageLinkInfo -> Encoding
toJSON :: GetMessageLinkInfo -> Value
$ctoJSON :: GetMessageLinkInfo -> Value
parseJSONList :: Value -> Parser [GetMessageLinkInfo]
$cparseJSONList :: Value -> Parser [GetMessageLinkInfo]
parseJSON :: Value -> Parser GetMessageLinkInfo
$cparseJSON :: Value -> Parser GetMessageLinkInfo
toEncodingList :: [SendMessage] -> Encoding
$ctoEncodingList :: [SendMessage] -> Encoding
toJSONList :: [SendMessage] -> Value
$ctoJSONList :: [SendMessage] -> Value
toEncoding :: SendMessage -> Encoding
$ctoEncoding :: SendMessage -> Encoding
toJSON :: SendMessage -> Value
$ctoJSON :: SendMessage -> Value
parseJSONList :: Value -> Parser [SendMessage]
$cparseJSONList :: Value -> Parser [SendMessage]
parseJSON :: Value -> Parser SendMessage
$cparseJSON :: Value -> Parser SendMessage
toEncodingList :: [SendMessageAlbum] -> Encoding
$ctoEncodingList :: [SendMessageAlbum] -> Encoding
toJSONList :: [SendMessageAlbum] -> Value
$ctoJSONList :: [SendMessageAlbum] -> Value
toEncoding :: SendMessageAlbum -> Encoding
$ctoEncoding :: SendMessageAlbum -> Encoding
toJSON :: SendMessageAlbum -> Value
$ctoJSON :: SendMessageAlbum -> Value
parseJSONList :: Value -> Parser [SendMessageAlbum]
$cparseJSONList :: Value -> Parser [SendMessageAlbum]
parseJSON :: Value -> Parser SendMessageAlbum
$cparseJSON :: Value -> Parser SendMessageAlbum
toEncodingList :: [SendBotStartMessage] -> Encoding
$ctoEncodingList :: [SendBotStartMessage] -> Encoding
toJSONList :: [SendBotStartMessage] -> Value
$ctoJSONList :: [SendBotStartMessage] -> Value
toEncoding :: SendBotStartMessage -> Encoding
$ctoEncoding :: SendBotStartMessage -> Encoding
toJSON :: SendBotStartMessage -> Value
$ctoJSON :: SendBotStartMessage -> Value
parseJSONList :: Value -> Parser [SendBotStartMessage]
$cparseJSONList :: Value -> Parser [SendBotStartMessage]
parseJSON :: Value -> Parser SendBotStartMessage
$cparseJSON :: Value -> Parser SendBotStartMessage
toEncodingList :: [SendInlineQueryResultMessage] -> Encoding
$ctoEncodingList :: [SendInlineQueryResultMessage] -> Encoding
toJSONList :: [SendInlineQueryResultMessage] -> Value
$ctoJSONList :: [SendInlineQueryResultMessage] -> Value
toEncoding :: SendInlineQueryResultMessage -> Encoding
$ctoEncoding :: SendInlineQueryResultMessage -> Encoding
toJSON :: SendInlineQueryResultMessage -> Value
$ctoJSON :: SendInlineQueryResultMessage -> Value
parseJSONList :: Value -> Parser [SendInlineQueryResultMessage]
$cparseJSONList :: Value -> Parser [SendInlineQueryResultMessage]
parseJSON :: Value -> Parser SendInlineQueryResultMessage
$cparseJSON :: Value -> Parser SendInlineQueryResultMessage
toEncodingList :: [ForwardMessages] -> Encoding
$ctoEncodingList :: [ForwardMessages] -> Encoding
toJSONList :: [ForwardMessages] -> Value
$ctoJSONList :: [ForwardMessages] -> Value
toEncoding :: ForwardMessages -> Encoding
$ctoEncoding :: ForwardMessages -> Encoding
toJSON :: ForwardMessages -> Value
$ctoJSON :: ForwardMessages -> Value
parseJSONList :: Value -> Parser [ForwardMessages]
$cparseJSONList :: Value -> Parser [ForwardMessages]
parseJSON :: Value -> Parser ForwardMessages
$cparseJSON :: Value -> Parser ForwardMessages
toEncodingList :: [ResendMessages] -> Encoding
$ctoEncodingList :: [ResendMessages] -> Encoding
toJSONList :: [ResendMessages] -> Value
$ctoJSONList :: [ResendMessages] -> Value
toEncoding :: ResendMessages -> Encoding
$ctoEncoding :: ResendMessages -> Encoding
toJSON :: ResendMessages -> Value
$ctoJSON :: ResendMessages -> Value
parseJSONList :: Value -> Parser [ResendMessages]
$cparseJSONList :: Value -> Parser [ResendMessages]
parseJSON :: Value -> Parser ResendMessages
$cparseJSON :: Value -> Parser ResendMessages
toEncodingList :: [SendChatSetTtlMessage] -> Encoding
$ctoEncodingList :: [SendChatSetTtlMessage] -> Encoding
toJSONList :: [SendChatSetTtlMessage] -> Value
$ctoJSONList :: [SendChatSetTtlMessage] -> Value
toEncoding :: SendChatSetTtlMessage -> Encoding
$ctoEncoding :: SendChatSetTtlMessage -> Encoding
toJSON :: SendChatSetTtlMessage -> Value
$ctoJSON :: SendChatSetTtlMessage -> Value
parseJSONList :: Value -> Parser [SendChatSetTtlMessage]
$cparseJSONList :: Value -> Parser [SendChatSetTtlMessage]
parseJSON :: Value -> Parser SendChatSetTtlMessage
$cparseJSON :: Value -> Parser SendChatSetTtlMessage
toEncodingList :: [SendChatScreenshotTakenNotification] -> Encoding
$ctoEncodingList :: [SendChatScreenshotTakenNotification] -> Encoding
toJSONList :: [SendChatScreenshotTakenNotification] -> Value
$ctoJSONList :: [SendChatScreenshotTakenNotification] -> Value
toEncoding :: SendChatScreenshotTakenNotification -> Encoding
$ctoEncoding :: SendChatScreenshotTakenNotification -> Encoding
toJSON :: SendChatScreenshotTakenNotification -> Value
$ctoJSON :: SendChatScreenshotTakenNotification -> Value
parseJSONList :: Value -> Parser [SendChatScreenshotTakenNotification]
$cparseJSONList :: Value -> Parser [SendChatScreenshotTakenNotification]
parseJSON :: Value -> Parser SendChatScreenshotTakenNotification
$cparseJSON :: Value -> Parser SendChatScreenshotTakenNotification
toEncodingList :: [AddLocalMessage] -> Encoding
$ctoEncodingList :: [AddLocalMessage] -> Encoding
toJSONList :: [AddLocalMessage] -> Value
$ctoJSONList :: [AddLocalMessage] -> Value
toEncoding :: AddLocalMessage -> Encoding
$ctoEncoding :: AddLocalMessage -> Encoding
toJSON :: AddLocalMessage -> Value
$ctoJSON :: AddLocalMessage -> Value
parseJSONList :: Value -> Parser [AddLocalMessage]
$cparseJSONList :: Value -> Parser [AddLocalMessage]
parseJSON :: Value -> Parser AddLocalMessage
$cparseJSON :: Value -> Parser AddLocalMessage
toEncodingList :: [DeleteMessages] -> Encoding
$ctoEncodingList :: [DeleteMessages] -> Encoding
toJSONList :: [DeleteMessages] -> Value
$ctoJSONList :: [DeleteMessages] -> Value
toEncoding :: DeleteMessages -> Encoding
$ctoEncoding :: DeleteMessages -> Encoding
toJSON :: DeleteMessages -> Value
$ctoJSON :: DeleteMessages -> Value
parseJSONList :: Value -> Parser [DeleteMessages]
$cparseJSONList :: Value -> Parser [DeleteMessages]
parseJSON :: Value -> Parser DeleteMessages
$cparseJSON :: Value -> Parser DeleteMessages
toEncodingList :: [DeleteChatMessagesFromUser] -> Encoding
$ctoEncodingList :: [DeleteChatMessagesFromUser] -> Encoding
toJSONList :: [DeleteChatMessagesFromUser] -> Value
$ctoJSONList :: [DeleteChatMessagesFromUser] -> Value
toEncoding :: DeleteChatMessagesFromUser -> Encoding
$ctoEncoding :: DeleteChatMessagesFromUser -> Encoding
toJSON :: DeleteChatMessagesFromUser -> Value
$ctoJSON :: DeleteChatMessagesFromUser -> Value
parseJSONList :: Value -> Parser [DeleteChatMessagesFromUser]
$cparseJSONList :: Value -> Parser [DeleteChatMessagesFromUser]
parseJSON :: Value -> Parser DeleteChatMessagesFromUser
$cparseJSON :: Value -> Parser DeleteChatMessagesFromUser
toEncodingList :: [EditMessageText] -> Encoding
$ctoEncodingList :: [EditMessageText] -> Encoding
toJSONList :: [EditMessageText] -> Value
$ctoJSONList :: [EditMessageText] -> Value
toEncoding :: EditMessageText -> Encoding
$ctoEncoding :: EditMessageText -> Encoding
toJSON :: EditMessageText -> Value
$ctoJSON :: EditMessageText -> Value
parseJSONList :: Value -> Parser [EditMessageText]
$cparseJSONList :: Value -> Parser [EditMessageText]
parseJSON :: Value -> Parser EditMessageText
$cparseJSON :: Value -> Parser EditMessageText
toEncodingList :: [EditMessageLiveLocation] -> Encoding
$ctoEncodingList :: [EditMessageLiveLocation] -> Encoding
toJSONList :: [EditMessageLiveLocation] -> Value
$ctoJSONList :: [EditMessageLiveLocation] -> Value
toEncoding :: EditMessageLiveLocation -> Encoding
$ctoEncoding :: EditMessageLiveLocation -> Encoding
toJSON :: EditMessageLiveLocation -> Value
$ctoJSON :: EditMessageLiveLocation -> Value
parseJSONList :: Value -> Parser [EditMessageLiveLocation]
$cparseJSONList :: Value -> Parser [EditMessageLiveLocation]
parseJSON :: Value -> Parser EditMessageLiveLocation
$cparseJSON :: Value -> Parser EditMessageLiveLocation
toEncodingList :: [EditMessageMedia] -> Encoding
$ctoEncodingList :: [EditMessageMedia] -> Encoding
toJSONList :: [EditMessageMedia] -> Value
$ctoJSONList :: [EditMessageMedia] -> Value
toEncoding :: EditMessageMedia -> Encoding
$ctoEncoding :: EditMessageMedia -> Encoding
toJSON :: EditMessageMedia -> Value
$ctoJSON :: EditMessageMedia -> Value
parseJSONList :: Value -> Parser [EditMessageMedia]
$cparseJSONList :: Value -> Parser [EditMessageMedia]
parseJSON :: Value -> Parser EditMessageMedia
$cparseJSON :: Value -> Parser EditMessageMedia
toEncodingList :: [EditMessageCaption] -> Encoding
$ctoEncodingList :: [EditMessageCaption] -> Encoding
toJSONList :: [EditMessageCaption] -> Value
$ctoJSONList :: [EditMessageCaption] -> Value
toEncoding :: EditMessageCaption -> Encoding
$ctoEncoding :: EditMessageCaption -> Encoding
toJSON :: EditMessageCaption -> Value
$ctoJSON :: EditMessageCaption -> Value
parseJSONList :: Value -> Parser [EditMessageCaption]
$cparseJSONList :: Value -> Parser [EditMessageCaption]
parseJSON :: Value -> Parser EditMessageCaption
$cparseJSON :: Value -> Parser EditMessageCaption
toEncodingList :: [EditMessageReplyMarkup] -> Encoding
$ctoEncodingList :: [EditMessageReplyMarkup] -> Encoding
toJSONList :: [EditMessageReplyMarkup] -> Value
$ctoJSONList :: [EditMessageReplyMarkup] -> Value
toEncoding :: EditMessageReplyMarkup -> Encoding
$ctoEncoding :: EditMessageReplyMarkup -> Encoding
toJSON :: EditMessageReplyMarkup -> Value
$ctoJSON :: EditMessageReplyMarkup -> Value
parseJSONList :: Value -> Parser [EditMessageReplyMarkup]
$cparseJSONList :: Value -> Parser [EditMessageReplyMarkup]
parseJSON :: Value -> Parser EditMessageReplyMarkup
$cparseJSON :: Value -> Parser EditMessageReplyMarkup
toEncodingList :: [EditInlineMessageText] -> Encoding
$ctoEncodingList :: [EditInlineMessageText] -> Encoding
toJSONList :: [EditInlineMessageText] -> Value
$ctoJSONList :: [EditInlineMessageText] -> Value
toEncoding :: EditInlineMessageText -> Encoding
$ctoEncoding :: EditInlineMessageText -> Encoding
toJSON :: EditInlineMessageText -> Value
$ctoJSON :: EditInlineMessageText -> Value
parseJSONList :: Value -> Parser [EditInlineMessageText]
$cparseJSONList :: Value -> Parser [EditInlineMessageText]
parseJSON :: Value -> Parser EditInlineMessageText
$cparseJSON :: Value -> Parser EditInlineMessageText
toEncodingList :: [EditInlineMessageLiveLocation] -> Encoding
$ctoEncodingList :: [EditInlineMessageLiveLocation] -> Encoding
toJSONList :: [EditInlineMessageLiveLocation] -> Value
$ctoJSONList :: [EditInlineMessageLiveLocation] -> Value
toEncoding :: EditInlineMessageLiveLocation -> Encoding
$ctoEncoding :: EditInlineMessageLiveLocation -> Encoding
toJSON :: EditInlineMessageLiveLocation -> Value
$ctoJSON :: EditInlineMessageLiveLocation -> Value
parseJSONList :: Value -> Parser [EditInlineMessageLiveLocation]
$cparseJSONList :: Value -> Parser [EditInlineMessageLiveLocation]
parseJSON :: Value -> Parser EditInlineMessageLiveLocation
$cparseJSON :: Value -> Parser EditInlineMessageLiveLocation
toEncodingList :: [EditInlineMessageMedia] -> Encoding
$ctoEncodingList :: [EditInlineMessageMedia] -> Encoding
toJSONList :: [EditInlineMessageMedia] -> Value
$ctoJSONList :: [EditInlineMessageMedia] -> Value
toEncoding :: EditInlineMessageMedia -> Encoding
$ctoEncoding :: EditInlineMessageMedia -> Encoding
toJSON :: EditInlineMessageMedia -> Value
$ctoJSON :: EditInlineMessageMedia -> Value
parseJSONList :: Value -> Parser [EditInlineMessageMedia]
$cparseJSONList :: Value -> Parser [EditInlineMessageMedia]
parseJSON :: Value -> Parser EditInlineMessageMedia
$cparseJSON :: Value -> Parser EditInlineMessageMedia
toEncodingList :: [EditInlineMessageCaption] -> Encoding
$ctoEncodingList :: [EditInlineMessageCaption] -> Encoding
toJSONList :: [EditInlineMessageCaption] -> Value
$ctoJSONList :: [EditInlineMessageCaption] -> Value
toEncoding :: EditInlineMessageCaption -> Encoding
$ctoEncoding :: EditInlineMessageCaption -> Encoding
toJSON :: EditInlineMessageCaption -> Value
$ctoJSON :: EditInlineMessageCaption -> Value
parseJSONList :: Value -> Parser [EditInlineMessageCaption]
$cparseJSONList :: Value -> Parser [EditInlineMessageCaption]
parseJSON :: Value -> Parser EditInlineMessageCaption
$cparseJSON :: Value -> Parser EditInlineMessageCaption
toEncodingList :: [EditInlineMessageReplyMarkup] -> Encoding
$ctoEncodingList :: [EditInlineMessageReplyMarkup] -> Encoding
toJSONList :: [EditInlineMessageReplyMarkup] -> Value
$ctoJSONList :: [EditInlineMessageReplyMarkup] -> Value
toEncoding :: EditInlineMessageReplyMarkup -> Encoding
$ctoEncoding :: EditInlineMessageReplyMarkup -> Encoding
toJSON :: EditInlineMessageReplyMarkup -> Value
$ctoJSON :: EditInlineMessageReplyMarkup -> Value
parseJSONList :: Value -> Parser [EditInlineMessageReplyMarkup]
$cparseJSONList :: Value -> Parser [EditInlineMessageReplyMarkup]
parseJSON :: Value -> Parser EditInlineMessageReplyMarkup
$cparseJSON :: Value -> Parser EditInlineMessageReplyMarkup
toEncodingList :: [EditMessageSchedulingState] -> Encoding
$ctoEncodingList :: [EditMessageSchedulingState] -> Encoding
toJSONList :: [EditMessageSchedulingState] -> Value
$ctoJSONList :: [EditMessageSchedulingState] -> Value
toEncoding :: EditMessageSchedulingState -> Encoding
$ctoEncoding :: EditMessageSchedulingState -> Encoding
toJSON :: EditMessageSchedulingState -> Value
$ctoJSON :: EditMessageSchedulingState -> Value
parseJSONList :: Value -> Parser [EditMessageSchedulingState]
$cparseJSONList :: Value -> Parser [EditMessageSchedulingState]
parseJSON :: Value -> Parser EditMessageSchedulingState
$cparseJSON :: Value -> Parser EditMessageSchedulingState
toEncodingList :: [GetTextEntities] -> Encoding
$ctoEncodingList :: [GetTextEntities] -> Encoding
toJSONList :: [GetTextEntities] -> Value
$ctoJSONList :: [GetTextEntities] -> Value
toEncoding :: GetTextEntities -> Encoding
$ctoEncoding :: GetTextEntities -> Encoding
toJSON :: GetTextEntities -> Value
$ctoJSON :: GetTextEntities -> Value
parseJSONList :: Value -> Parser [GetTextEntities]
$cparseJSONList :: Value -> Parser [GetTextEntities]
parseJSON :: Value -> Parser GetTextEntities
$cparseJSON :: Value -> Parser GetTextEntities
toEncodingList :: [ParseTextEntities] -> Encoding
$ctoEncodingList :: [ParseTextEntities] -> Encoding
toJSONList :: [ParseTextEntities] -> Value
$ctoJSONList :: [ParseTextEntities] -> Value
toEncoding :: ParseTextEntities -> Encoding
$ctoEncoding :: ParseTextEntities -> Encoding
toJSON :: ParseTextEntities -> Value
$ctoJSON :: ParseTextEntities -> Value
parseJSONList :: Value -> Parser [ParseTextEntities]
$cparseJSONList :: Value -> Parser [ParseTextEntities]
parseJSON :: Value -> Parser ParseTextEntities
$cparseJSON :: Value -> Parser ParseTextEntities
toEncodingList :: [ParseMarkdown] -> Encoding
$ctoEncodingList :: [ParseMarkdown] -> Encoding
toJSONList :: [ParseMarkdown] -> Value
$ctoJSONList :: [ParseMarkdown] -> Value
toEncoding :: ParseMarkdown -> Encoding
$ctoEncoding :: ParseMarkdown -> Encoding
toJSON :: ParseMarkdown -> Value
$ctoJSON :: ParseMarkdown -> Value
parseJSONList :: Value -> Parser [ParseMarkdown]
$cparseJSONList :: Value -> Parser [ParseMarkdown]
parseJSON :: Value -> Parser ParseMarkdown
$cparseJSON :: Value -> Parser ParseMarkdown
toEncodingList :: [GetMarkdownText] -> Encoding
$ctoEncodingList :: [GetMarkdownText] -> Encoding
toJSONList :: [GetMarkdownText] -> Value
$ctoJSONList :: [GetMarkdownText] -> Value
toEncoding :: GetMarkdownText -> Encoding
$ctoEncoding :: GetMarkdownText -> Encoding
toJSON :: GetMarkdownText -> Value
$ctoJSON :: GetMarkdownText -> Value
parseJSONList :: Value -> Parser [GetMarkdownText]
$cparseJSONList :: Value -> Parser [GetMarkdownText]
parseJSON :: Value -> Parser GetMarkdownText
$cparseJSON :: Value -> Parser GetMarkdownText
toEncodingList :: [GetFileMimeType] -> Encoding
$ctoEncodingList :: [GetFileMimeType] -> Encoding
toJSONList :: [GetFileMimeType] -> Value
$ctoJSONList :: [GetFileMimeType] -> Value
toEncoding :: GetFileMimeType -> Encoding
$ctoEncoding :: GetFileMimeType -> Encoding
toJSON :: GetFileMimeType -> Value
$ctoJSON :: GetFileMimeType -> Value
parseJSONList :: Value -> Parser [GetFileMimeType]
$cparseJSONList :: Value -> Parser [GetFileMimeType]
parseJSON :: Value -> Parser GetFileMimeType
$cparseJSON :: Value -> Parser GetFileMimeType
toEncodingList :: [GetFileExtension] -> Encoding
$ctoEncodingList :: [GetFileExtension] -> Encoding
toJSONList :: [GetFileExtension] -> Value
$ctoJSONList :: [GetFileExtension] -> Value
toEncoding :: GetFileExtension -> Encoding
$ctoEncoding :: GetFileExtension -> Encoding
toJSON :: GetFileExtension -> Value
$ctoJSON :: GetFileExtension -> Value
parseJSONList :: Value -> Parser [GetFileExtension]
$cparseJSONList :: Value -> Parser [GetFileExtension]
parseJSON :: Value -> Parser GetFileExtension
$cparseJSON :: Value -> Parser GetFileExtension
toEncodingList :: [CleanFileName] -> Encoding
$ctoEncodingList :: [CleanFileName] -> Encoding
toJSONList :: [CleanFileName] -> Value
$ctoJSONList :: [CleanFileName] -> Value
toEncoding :: CleanFileName -> Encoding
$ctoEncoding :: CleanFileName -> Encoding
toJSON :: CleanFileName -> Value
$ctoJSON :: CleanFileName -> Value
parseJSONList :: Value -> Parser [CleanFileName]
$cparseJSONList :: Value -> Parser [CleanFileName]
parseJSON :: Value -> Parser CleanFileName
$cparseJSON :: Value -> Parser CleanFileName
toEncodingList :: [GetLanguagePackString] -> Encoding
$ctoEncodingList :: [GetLanguagePackString] -> Encoding
toJSONList :: [GetLanguagePackString] -> Value
$ctoJSONList :: [GetLanguagePackString] -> Value
toEncoding :: GetLanguagePackString -> Encoding
$ctoEncoding :: GetLanguagePackString -> Encoding
toJSON :: GetLanguagePackString -> Value
$ctoJSON :: GetLanguagePackString -> Value
parseJSONList :: Value -> Parser [GetLanguagePackString]
$cparseJSONList :: Value -> Parser [GetLanguagePackString]
parseJSON :: Value -> Parser GetLanguagePackString
$cparseJSON :: Value -> Parser GetLanguagePackString
toEncodingList :: [GetJsonValue] -> Encoding
$ctoEncodingList :: [GetJsonValue] -> Encoding
toJSONList :: [GetJsonValue] -> Value
$ctoJSONList :: [GetJsonValue] -> Value
toEncoding :: GetJsonValue -> Encoding
$ctoEncoding :: GetJsonValue -> Encoding
toJSON :: GetJsonValue -> Value
$ctoJSON :: GetJsonValue -> Value
parseJSONList :: Value -> Parser [GetJsonValue]
$cparseJSONList :: Value -> Parser [GetJsonValue]
parseJSON :: Value -> Parser GetJsonValue
$cparseJSON :: Value -> Parser GetJsonValue
toEncodingList :: [GetJsonString] -> Encoding
$ctoEncodingList :: [GetJsonString] -> Encoding
toJSONList :: [GetJsonString] -> Value
$ctoJSONList :: [GetJsonString] -> Value
toEncoding :: GetJsonString -> Encoding
$ctoEncoding :: GetJsonString -> Encoding
toJSON :: GetJsonString -> Value
$ctoJSON :: GetJsonString -> Value
parseJSONList :: Value -> Parser [GetJsonString]
$cparseJSONList :: Value -> Parser [GetJsonString]
parseJSON :: Value -> Parser GetJsonString
$cparseJSON :: Value -> Parser GetJsonString
toEncodingList :: [SetPollAnswer] -> Encoding
$ctoEncodingList :: [SetPollAnswer] -> Encoding
toJSONList :: [SetPollAnswer] -> Value
$ctoJSONList :: [SetPollAnswer] -> Value
toEncoding :: SetPollAnswer -> Encoding
$ctoEncoding :: SetPollAnswer -> Encoding
toJSON :: SetPollAnswer -> Value
$ctoJSON :: SetPollAnswer -> Value
parseJSONList :: Value -> Parser [SetPollAnswer]
$cparseJSONList :: Value -> Parser [SetPollAnswer]
parseJSON :: Value -> Parser SetPollAnswer
$cparseJSON :: Value -> Parser SetPollAnswer
toEncodingList :: [GetPollVoters] -> Encoding
$ctoEncodingList :: [GetPollVoters] -> Encoding
toJSONList :: [GetPollVoters] -> Value
$ctoJSONList :: [GetPollVoters] -> Value
toEncoding :: GetPollVoters -> Encoding
$ctoEncoding :: GetPollVoters -> Encoding
toJSON :: GetPollVoters -> Value
$ctoJSON :: GetPollVoters -> Value
parseJSONList :: Value -> Parser [GetPollVoters]
$cparseJSONList :: Value -> Parser [GetPollVoters]
parseJSON :: Value -> Parser GetPollVoters
$cparseJSON :: Value -> Parser GetPollVoters
toEncodingList :: [StopPoll] -> Encoding
$ctoEncodingList :: [StopPoll] -> Encoding
toJSONList :: [StopPoll] -> Value
$ctoJSONList :: [StopPoll] -> Value
toEncoding :: StopPoll -> Encoding
$ctoEncoding :: StopPoll -> Encoding
toJSON :: StopPoll -> Value
$ctoJSON :: StopPoll -> Value
parseJSONList :: Value -> Parser [StopPoll]
$cparseJSONList :: Value -> Parser [StopPoll]
parseJSON :: Value -> Parser StopPoll
$cparseJSON :: Value -> Parser StopPoll
toEncodingList :: [GetLoginUrlInfo] -> Encoding
$ctoEncodingList :: [GetLoginUrlInfo] -> Encoding
toJSONList :: [GetLoginUrlInfo] -> Value
$ctoJSONList :: [GetLoginUrlInfo] -> Value
toEncoding :: GetLoginUrlInfo -> Encoding
$ctoEncoding :: GetLoginUrlInfo -> Encoding
toJSON :: GetLoginUrlInfo -> Value
$ctoJSON :: GetLoginUrlInfo -> Value
parseJSONList :: Value -> Parser [GetLoginUrlInfo]
$cparseJSONList :: Value -> Parser [GetLoginUrlInfo]
parseJSON :: Value -> Parser GetLoginUrlInfo
$cparseJSON :: Value -> Parser GetLoginUrlInfo
toEncodingList :: [GetLoginUrl] -> Encoding
$ctoEncodingList :: [GetLoginUrl] -> Encoding
toJSONList :: [GetLoginUrl] -> Value
$ctoJSONList :: [GetLoginUrl] -> Value
toEncoding :: GetLoginUrl -> Encoding
$ctoEncoding :: GetLoginUrl -> Encoding
toJSON :: GetLoginUrl -> Value
$ctoJSON :: GetLoginUrl -> Value
parseJSONList :: Value -> Parser [GetLoginUrl]
$cparseJSONList :: Value -> Parser [GetLoginUrl]
parseJSON :: Value -> Parser GetLoginUrl
$cparseJSON :: Value -> Parser GetLoginUrl
toEncodingList :: [GetInlineQueryResults] -> Encoding
$ctoEncodingList :: [GetInlineQueryResults] -> Encoding
toJSONList :: [GetInlineQueryResults] -> Value
$ctoJSONList :: [GetInlineQueryResults] -> Value
toEncoding :: GetInlineQueryResults -> Encoding
$ctoEncoding :: GetInlineQueryResults -> Encoding
toJSON :: GetInlineQueryResults -> Value
$ctoJSON :: GetInlineQueryResults -> Value
parseJSONList :: Value -> Parser [GetInlineQueryResults]
$cparseJSONList :: Value -> Parser [GetInlineQueryResults]
parseJSON :: Value -> Parser GetInlineQueryResults
$cparseJSON :: Value -> Parser GetInlineQueryResults
toEncodingList :: [AnswerInlineQuery] -> Encoding
$ctoEncodingList :: [AnswerInlineQuery] -> Encoding
toJSONList :: [AnswerInlineQuery] -> Value
$ctoJSONList :: [AnswerInlineQuery] -> Value
toEncoding :: AnswerInlineQuery -> Encoding
$ctoEncoding :: AnswerInlineQuery -> Encoding
toJSON :: AnswerInlineQuery -> Value
$ctoJSON :: AnswerInlineQuery -> Value
parseJSONList :: Value -> Parser [AnswerInlineQuery]
$cparseJSONList :: Value -> Parser [AnswerInlineQuery]
parseJSON :: Value -> Parser AnswerInlineQuery
$cparseJSON :: Value -> Parser AnswerInlineQuery
toEncodingList :: [GetCallbackQueryAnswer] -> Encoding
$ctoEncodingList :: [GetCallbackQueryAnswer] -> Encoding
toJSONList :: [GetCallbackQueryAnswer] -> Value
$ctoJSONList :: [GetCallbackQueryAnswer] -> Value
toEncoding :: GetCallbackQueryAnswer -> Encoding
$ctoEncoding :: GetCallbackQueryAnswer -> Encoding
toJSON :: GetCallbackQueryAnswer -> Value
$ctoJSON :: GetCallbackQueryAnswer -> Value
parseJSONList :: Value -> Parser [GetCallbackQueryAnswer]
$cparseJSONList :: Value -> Parser [GetCallbackQueryAnswer]
parseJSON :: Value -> Parser GetCallbackQueryAnswer
$cparseJSON :: Value -> Parser GetCallbackQueryAnswer
toEncodingList :: [AnswerCallbackQuery] -> Encoding
$ctoEncodingList :: [AnswerCallbackQuery] -> Encoding
toJSONList :: [AnswerCallbackQuery] -> Value
$ctoJSONList :: [AnswerCallbackQuery] -> Value
toEncoding :: AnswerCallbackQuery -> Encoding
$ctoEncoding :: AnswerCallbackQuery -> Encoding
toJSON :: AnswerCallbackQuery -> Value
$ctoJSON :: AnswerCallbackQuery -> Value
parseJSONList :: Value -> Parser [AnswerCallbackQuery]
$cparseJSONList :: Value -> Parser [AnswerCallbackQuery]
parseJSON :: Value -> Parser AnswerCallbackQuery
$cparseJSON :: Value -> Parser AnswerCallbackQuery
toEncodingList :: [AnswerShippingQuery] -> Encoding
$ctoEncodingList :: [AnswerShippingQuery] -> Encoding
toJSONList :: [AnswerShippingQuery] -> Value
$ctoJSONList :: [AnswerShippingQuery] -> Value
toEncoding :: AnswerShippingQuery -> Encoding
$ctoEncoding :: AnswerShippingQuery -> Encoding
toJSON :: AnswerShippingQuery -> Value
$ctoJSON :: AnswerShippingQuery -> Value
parseJSONList :: Value -> Parser [AnswerShippingQuery]
$cparseJSONList :: Value -> Parser [AnswerShippingQuery]
parseJSON :: Value -> Parser AnswerShippingQuery
$cparseJSON :: Value -> Parser AnswerShippingQuery
toEncodingList :: [AnswerPreCheckoutQuery] -> Encoding
$ctoEncodingList :: [AnswerPreCheckoutQuery] -> Encoding
toJSONList :: [AnswerPreCheckoutQuery] -> Value
$ctoJSONList :: [AnswerPreCheckoutQuery] -> Value
toEncoding :: AnswerPreCheckoutQuery -> Encoding
$ctoEncoding :: AnswerPreCheckoutQuery -> Encoding
toJSON :: AnswerPreCheckoutQuery -> Value
$ctoJSON :: AnswerPreCheckoutQuery -> Value
parseJSONList :: Value -> Parser [AnswerPreCheckoutQuery]
$cparseJSONList :: Value -> Parser [AnswerPreCheckoutQuery]
parseJSON :: Value -> Parser AnswerPreCheckoutQuery
$cparseJSON :: Value -> Parser AnswerPreCheckoutQuery
toEncodingList :: [SetGameScore] -> Encoding
$ctoEncodingList :: [SetGameScore] -> Encoding
toJSONList :: [SetGameScore] -> Value
$ctoJSONList :: [SetGameScore] -> Value
toEncoding :: SetGameScore -> Encoding
$ctoEncoding :: SetGameScore -> Encoding
toJSON :: SetGameScore -> Value
$ctoJSON :: SetGameScore -> Value
parseJSONList :: Value -> Parser [SetGameScore]
$cparseJSONList :: Value -> Parser [SetGameScore]
parseJSON :: Value -> Parser SetGameScore
$cparseJSON :: Value -> Parser SetGameScore
toEncodingList :: [SetInlineGameScore] -> Encoding
$ctoEncodingList :: [SetInlineGameScore] -> Encoding
toJSONList :: [SetInlineGameScore] -> Value
$ctoJSONList :: [SetInlineGameScore] -> Value
toEncoding :: SetInlineGameScore -> Encoding
$ctoEncoding :: SetInlineGameScore -> Encoding
toJSON :: SetInlineGameScore -> Value
$ctoJSON :: SetInlineGameScore -> Value
parseJSONList :: Value -> Parser [SetInlineGameScore]
$cparseJSONList :: Value -> Parser [SetInlineGameScore]
parseJSON :: Value -> Parser SetInlineGameScore
$cparseJSON :: Value -> Parser SetInlineGameScore
toEncodingList :: [GetGameHighScores] -> Encoding
$ctoEncodingList :: [GetGameHighScores] -> Encoding
toJSONList :: [GetGameHighScores] -> Value
$ctoJSONList :: [GetGameHighScores] -> Value
toEncoding :: GetGameHighScores -> Encoding
$ctoEncoding :: GetGameHighScores -> Encoding
toJSON :: GetGameHighScores -> Value
$ctoJSON :: GetGameHighScores -> Value
parseJSONList :: Value -> Parser [GetGameHighScores]
$cparseJSONList :: Value -> Parser [GetGameHighScores]
parseJSON :: Value -> Parser GetGameHighScores
$cparseJSON :: Value -> Parser GetGameHighScores
toEncodingList :: [GetInlineGameHighScores] -> Encoding
$ctoEncodingList :: [GetInlineGameHighScores] -> Encoding
toJSONList :: [GetInlineGameHighScores] -> Value
$ctoJSONList :: [GetInlineGameHighScores] -> Value
toEncoding :: GetInlineGameHighScores -> Encoding
$ctoEncoding :: GetInlineGameHighScores -> Encoding
toJSON :: GetInlineGameHighScores -> Value
$ctoJSON :: GetInlineGameHighScores -> Value
parseJSONList :: Value -> Parser [GetInlineGameHighScores]
$cparseJSONList :: Value -> Parser [GetInlineGameHighScores]
parseJSON :: Value -> Parser GetInlineGameHighScores
$cparseJSON :: Value -> Parser GetInlineGameHighScores
toEncodingList :: [DeleteChatReplyMarkup] -> Encoding
$ctoEncodingList :: [DeleteChatReplyMarkup] -> Encoding
toJSONList :: [DeleteChatReplyMarkup] -> Value
$ctoJSONList :: [DeleteChatReplyMarkup] -> Value
toEncoding :: DeleteChatReplyMarkup -> Encoding
$ctoEncoding :: DeleteChatReplyMarkup -> Encoding
toJSON :: DeleteChatReplyMarkup -> Value
$ctoJSON :: DeleteChatReplyMarkup -> Value
parseJSONList :: Value -> Parser [DeleteChatReplyMarkup]
$cparseJSONList :: Value -> Parser [DeleteChatReplyMarkup]
parseJSON :: Value -> Parser DeleteChatReplyMarkup
$cparseJSON :: Value -> Parser DeleteChatReplyMarkup
toEncodingList :: [SendChatAction] -> Encoding
$ctoEncodingList :: [SendChatAction] -> Encoding
toJSONList :: [SendChatAction] -> Value
$ctoJSONList :: [SendChatAction] -> Value
toEncoding :: SendChatAction -> Encoding
$ctoEncoding :: SendChatAction -> Encoding
toJSON :: SendChatAction -> Value
$ctoJSON :: SendChatAction -> Value
parseJSONList :: Value -> Parser [SendChatAction]
$cparseJSONList :: Value -> Parser [SendChatAction]
parseJSON :: Value -> Parser SendChatAction
$cparseJSON :: Value -> Parser SendChatAction
toEncodingList :: [OpenChat] -> Encoding
$ctoEncodingList :: [OpenChat] -> Encoding
toJSONList :: [OpenChat] -> Value
$ctoJSONList :: [OpenChat] -> Value
toEncoding :: OpenChat -> Encoding
$ctoEncoding :: OpenChat -> Encoding
toJSON :: OpenChat -> Value
$ctoJSON :: OpenChat -> Value
parseJSONList :: Value -> Parser [OpenChat]
$cparseJSONList :: Value -> Parser [OpenChat]
parseJSON :: Value -> Parser OpenChat
$cparseJSON :: Value -> Parser OpenChat
toEncodingList :: [CloseChat] -> Encoding
$ctoEncodingList :: [CloseChat] -> Encoding
toJSONList :: [CloseChat] -> Value
$ctoJSONList :: [CloseChat] -> Value
toEncoding :: CloseChat -> Encoding
$ctoEncoding :: CloseChat -> Encoding
toJSON :: CloseChat -> Value
$ctoJSON :: CloseChat -> Value
parseJSONList :: Value -> Parser [CloseChat]
$cparseJSONList :: Value -> Parser [CloseChat]
parseJSON :: Value -> Parser CloseChat
$cparseJSON :: Value -> Parser CloseChat
toEncodingList :: [ViewMessages] -> Encoding
$ctoEncodingList :: [ViewMessages] -> Encoding
toJSONList :: [ViewMessages] -> Value
$ctoJSONList :: [ViewMessages] -> Value
toEncoding :: ViewMessages -> Encoding
$ctoEncoding :: ViewMessages -> Encoding
toJSON :: ViewMessages -> Value
$ctoJSON :: ViewMessages -> Value
parseJSONList :: Value -> Parser [ViewMessages]
$cparseJSONList :: Value -> Parser [ViewMessages]
parseJSON :: Value -> Parser ViewMessages
$cparseJSON :: Value -> Parser ViewMessages
toEncodingList :: [OpenMessageContent] -> Encoding
$ctoEncodingList :: [OpenMessageContent] -> Encoding
toJSONList :: [OpenMessageContent] -> Value
$ctoJSONList :: [OpenMessageContent] -> Value
toEncoding :: OpenMessageContent -> Encoding
$ctoEncoding :: OpenMessageContent -> Encoding
toJSON :: OpenMessageContent -> Value
$ctoJSON :: OpenMessageContent -> Value
parseJSONList :: Value -> Parser [OpenMessageContent]
$cparseJSONList :: Value -> Parser [OpenMessageContent]
parseJSON :: Value -> Parser OpenMessageContent
$cparseJSON :: Value -> Parser OpenMessageContent
toEncodingList :: [ReadAllChatMentions] -> Encoding
$ctoEncodingList :: [ReadAllChatMentions] -> Encoding
toJSONList :: [ReadAllChatMentions] -> Value
$ctoJSONList :: [ReadAllChatMentions] -> Value
toEncoding :: ReadAllChatMentions -> Encoding
$ctoEncoding :: ReadAllChatMentions -> Encoding
toJSON :: ReadAllChatMentions -> Value
$ctoJSON :: ReadAllChatMentions -> Value
parseJSONList :: Value -> Parser [ReadAllChatMentions]
$cparseJSONList :: Value -> Parser [ReadAllChatMentions]
parseJSON :: Value -> Parser ReadAllChatMentions
$cparseJSON :: Value -> Parser ReadAllChatMentions
toEncodingList :: [CreatePrivateChat] -> Encoding
$ctoEncodingList :: [CreatePrivateChat] -> Encoding
toJSONList :: [CreatePrivateChat] -> Value
$ctoJSONList :: [CreatePrivateChat] -> Value
toEncoding :: CreatePrivateChat -> Encoding
$ctoEncoding :: CreatePrivateChat -> Encoding
toJSON :: CreatePrivateChat -> Value
$ctoJSON :: CreatePrivateChat -> Value
parseJSONList :: Value -> Parser [CreatePrivateChat]
$cparseJSONList :: Value -> Parser [CreatePrivateChat]
parseJSON :: Value -> Parser CreatePrivateChat
$cparseJSON :: Value -> Parser CreatePrivateChat
toEncodingList :: [CreateBasicGroupChat] -> Encoding
$ctoEncodingList :: [CreateBasicGroupChat] -> Encoding
toJSONList :: [CreateBasicGroupChat] -> Value
$ctoJSONList :: [CreateBasicGroupChat] -> Value
toEncoding :: CreateBasicGroupChat -> Encoding
$ctoEncoding :: CreateBasicGroupChat -> Encoding
toJSON :: CreateBasicGroupChat -> Value
$ctoJSON :: CreateBasicGroupChat -> Value
parseJSONList :: Value -> Parser [CreateBasicGroupChat]
$cparseJSONList :: Value -> Parser [CreateBasicGroupChat]
parseJSON :: Value -> Parser CreateBasicGroupChat
$cparseJSON :: Value -> Parser CreateBasicGroupChat
toEncodingList :: [CreateSupergroupChat] -> Encoding
$ctoEncodingList :: [CreateSupergroupChat] -> Encoding
toJSONList :: [CreateSupergroupChat] -> Value
$ctoJSONList :: [CreateSupergroupChat] -> Value
toEncoding :: CreateSupergroupChat -> Encoding
$ctoEncoding :: CreateSupergroupChat -> Encoding
toJSON :: CreateSupergroupChat -> Value
$ctoJSON :: CreateSupergroupChat -> Value
parseJSONList :: Value -> Parser [CreateSupergroupChat]
$cparseJSONList :: Value -> Parser [CreateSupergroupChat]
parseJSON :: Value -> Parser CreateSupergroupChat
$cparseJSON :: Value -> Parser CreateSupergroupChat
toEncodingList :: [CreateSecretChat] -> Encoding
$ctoEncodingList :: [CreateSecretChat] -> Encoding
toJSONList :: [CreateSecretChat] -> Value
$ctoJSONList :: [CreateSecretChat] -> Value
toEncoding :: CreateSecretChat -> Encoding
$ctoEncoding :: CreateSecretChat -> Encoding
toJSON :: CreateSecretChat -> Value
$ctoJSON :: CreateSecretChat -> Value
parseJSONList :: Value -> Parser [CreateSecretChat]
$cparseJSONList :: Value -> Parser [CreateSecretChat]
parseJSON :: Value -> Parser CreateSecretChat
$cparseJSON :: Value -> Parser CreateSecretChat
toEncodingList :: [CreateNewBasicGroupChat] -> Encoding
$ctoEncodingList :: [CreateNewBasicGroupChat] -> Encoding
toJSONList :: [CreateNewBasicGroupChat] -> Value
$ctoJSONList :: [CreateNewBasicGroupChat] -> Value
toEncoding :: CreateNewBasicGroupChat -> Encoding
$ctoEncoding :: CreateNewBasicGroupChat -> Encoding
toJSON :: CreateNewBasicGroupChat -> Value
$ctoJSON :: CreateNewBasicGroupChat -> Value
parseJSONList :: Value -> Parser [CreateNewBasicGroupChat]
$cparseJSONList :: Value -> Parser [CreateNewBasicGroupChat]
parseJSON :: Value -> Parser CreateNewBasicGroupChat
$cparseJSON :: Value -> Parser CreateNewBasicGroupChat
toEncodingList :: [CreateNewSupergroupChat] -> Encoding
$ctoEncodingList :: [CreateNewSupergroupChat] -> Encoding
toJSONList :: [CreateNewSupergroupChat] -> Value
$ctoJSONList :: [CreateNewSupergroupChat] -> Value
toEncoding :: CreateNewSupergroupChat -> Encoding
$ctoEncoding :: CreateNewSupergroupChat -> Encoding
toJSON :: CreateNewSupergroupChat -> Value
$ctoJSON :: CreateNewSupergroupChat -> Value
parseJSONList :: Value -> Parser [CreateNewSupergroupChat]
$cparseJSONList :: Value -> Parser [CreateNewSupergroupChat]
parseJSON :: Value -> Parser CreateNewSupergroupChat
$cparseJSON :: Value -> Parser CreateNewSupergroupChat
toEncodingList :: [CreateNewSecretChat] -> Encoding
$ctoEncodingList :: [CreateNewSecretChat] -> Encoding
toJSONList :: [CreateNewSecretChat] -> Value
$ctoJSONList :: [CreateNewSecretChat] -> Value
toEncoding :: CreateNewSecretChat -> Encoding
$ctoEncoding :: CreateNewSecretChat -> Encoding
toJSON :: CreateNewSecretChat -> Value
$ctoJSON :: CreateNewSecretChat -> Value
parseJSONList :: Value -> Parser [CreateNewSecretChat]
$cparseJSONList :: Value -> Parser [CreateNewSecretChat]
parseJSON :: Value -> Parser CreateNewSecretChat
$cparseJSON :: Value -> Parser CreateNewSecretChat
toEncodingList :: [UpgradeBasicGroupChatToSupergroupChat] -> Encoding
$ctoEncodingList :: [UpgradeBasicGroupChatToSupergroupChat] -> Encoding
toJSONList :: [UpgradeBasicGroupChatToSupergroupChat] -> Value
$ctoJSONList :: [UpgradeBasicGroupChatToSupergroupChat] -> Value
toEncoding :: UpgradeBasicGroupChatToSupergroupChat -> Encoding
$ctoEncoding :: UpgradeBasicGroupChatToSupergroupChat -> Encoding
toJSON :: UpgradeBasicGroupChatToSupergroupChat -> Value
$ctoJSON :: UpgradeBasicGroupChatToSupergroupChat -> Value
parseJSONList :: Value -> Parser [UpgradeBasicGroupChatToSupergroupChat]
$cparseJSONList :: Value -> Parser [UpgradeBasicGroupChatToSupergroupChat]
parseJSON :: Value -> Parser UpgradeBasicGroupChatToSupergroupChat
$cparseJSON :: Value -> Parser UpgradeBasicGroupChatToSupergroupChat
toEncodingList :: [SetChatChatList] -> Encoding
$ctoEncodingList :: [SetChatChatList] -> Encoding
toJSONList :: [SetChatChatList] -> Value
$ctoJSONList :: [SetChatChatList] -> Value
toEncoding :: SetChatChatList -> Encoding
$ctoEncoding :: SetChatChatList -> Encoding
toJSON :: SetChatChatList -> Value
$ctoJSON :: SetChatChatList -> Value
parseJSONList :: Value -> Parser [SetChatChatList]
$cparseJSONList :: Value -> Parser [SetChatChatList]
parseJSON :: Value -> Parser SetChatChatList
$cparseJSON :: Value -> Parser SetChatChatList
toEncodingList :: [SetChatTitle] -> Encoding
$ctoEncodingList :: [SetChatTitle] -> Encoding
toJSONList :: [SetChatTitle] -> Value
$ctoJSONList :: [SetChatTitle] -> Value
toEncoding :: SetChatTitle -> Encoding
$ctoEncoding :: SetChatTitle -> Encoding
toJSON :: SetChatTitle -> Value
$ctoJSON :: SetChatTitle -> Value
parseJSONList :: Value -> Parser [SetChatTitle]
$cparseJSONList :: Value -> Parser [SetChatTitle]
parseJSON :: Value -> Parser SetChatTitle
$cparseJSON :: Value -> Parser SetChatTitle
toEncodingList :: [SetChatPhoto] -> Encoding
$ctoEncodingList :: [SetChatPhoto] -> Encoding
toJSONList :: [SetChatPhoto] -> Value
$ctoJSONList :: [SetChatPhoto] -> Value
toEncoding :: SetChatPhoto -> Encoding
$ctoEncoding :: SetChatPhoto -> Encoding
toJSON :: SetChatPhoto -> Value
$ctoJSON :: SetChatPhoto -> Value
parseJSONList :: Value -> Parser [SetChatPhoto]
$cparseJSONList :: Value -> Parser [SetChatPhoto]
parseJSON :: Value -> Parser SetChatPhoto
$cparseJSON :: Value -> Parser SetChatPhoto
toEncodingList :: [SetChatPermissions] -> Encoding
$ctoEncodingList :: [SetChatPermissions] -> Encoding
toJSONList :: [SetChatPermissions] -> Value
$ctoJSONList :: [SetChatPermissions] -> Value
toEncoding :: SetChatPermissions -> Encoding
$ctoEncoding :: SetChatPermissions -> Encoding
toJSON :: SetChatPermissions -> Value
$ctoJSON :: SetChatPermissions -> Value
parseJSONList :: Value -> Parser [SetChatPermissions]
$cparseJSONList :: Value -> Parser [SetChatPermissions]
parseJSON :: Value -> Parser SetChatPermissions
$cparseJSON :: Value -> Parser SetChatPermissions
toEncodingList :: [SetChatDraftMessage] -> Encoding
$ctoEncodingList :: [SetChatDraftMessage] -> Encoding
toJSONList :: [SetChatDraftMessage] -> Value
$ctoJSONList :: [SetChatDraftMessage] -> Value
toEncoding :: SetChatDraftMessage -> Encoding
$ctoEncoding :: SetChatDraftMessage -> Encoding
toJSON :: SetChatDraftMessage -> Value
$ctoJSON :: SetChatDraftMessage -> Value
parseJSONList :: Value -> Parser [SetChatDraftMessage]
$cparseJSONList :: Value -> Parser [SetChatDraftMessage]
parseJSON :: Value -> Parser SetChatDraftMessage
$cparseJSON :: Value -> Parser SetChatDraftMessage
toEncodingList :: [SetChatNotificationSettings] -> Encoding
$ctoEncodingList :: [SetChatNotificationSettings] -> Encoding
toJSONList :: [SetChatNotificationSettings] -> Value
$ctoJSONList :: [SetChatNotificationSettings] -> Value
toEncoding :: SetChatNotificationSettings -> Encoding
$ctoEncoding :: SetChatNotificationSettings -> Encoding
toJSON :: SetChatNotificationSettings -> Value
$ctoJSON :: SetChatNotificationSettings -> Value
parseJSONList :: Value -> Parser [SetChatNotificationSettings]
$cparseJSONList :: Value -> Parser [SetChatNotificationSettings]
parseJSON :: Value -> Parser SetChatNotificationSettings
$cparseJSON :: Value -> Parser SetChatNotificationSettings
toEncodingList :: [ToggleChatIsPinned] -> Encoding
$ctoEncodingList :: [ToggleChatIsPinned] -> Encoding
toJSONList :: [ToggleChatIsPinned] -> Value
$ctoJSONList :: [ToggleChatIsPinned] -> Value
toEncoding :: ToggleChatIsPinned -> Encoding
$ctoEncoding :: ToggleChatIsPinned -> Encoding
toJSON :: ToggleChatIsPinned -> Value
$ctoJSON :: ToggleChatIsPinned -> Value
parseJSONList :: Value -> Parser [ToggleChatIsPinned]
$cparseJSONList :: Value -> Parser [ToggleChatIsPinned]
parseJSON :: Value -> Parser ToggleChatIsPinned
$cparseJSON :: Value -> Parser ToggleChatIsPinned
toEncodingList :: [ToggleChatIsMarkedAsUnread] -> Encoding
$ctoEncodingList :: [ToggleChatIsMarkedAsUnread] -> Encoding
toJSONList :: [ToggleChatIsMarkedAsUnread] -> Value
$ctoJSONList :: [ToggleChatIsMarkedAsUnread] -> Value
toEncoding :: ToggleChatIsMarkedAsUnread -> Encoding
$ctoEncoding :: ToggleChatIsMarkedAsUnread -> Encoding
toJSON :: ToggleChatIsMarkedAsUnread -> Value
$ctoJSON :: ToggleChatIsMarkedAsUnread -> Value
parseJSONList :: Value -> Parser [ToggleChatIsMarkedAsUnread]
$cparseJSONList :: Value -> Parser [ToggleChatIsMarkedAsUnread]
parseJSON :: Value -> Parser ToggleChatIsMarkedAsUnread
$cparseJSON :: Value -> Parser ToggleChatIsMarkedAsUnread
toEncodingList :: [ToggleChatDefaultDisableNotification] -> Encoding
$ctoEncodingList :: [ToggleChatDefaultDisableNotification] -> Encoding
toJSONList :: [ToggleChatDefaultDisableNotification] -> Value
$ctoJSONList :: [ToggleChatDefaultDisableNotification] -> Value
toEncoding :: ToggleChatDefaultDisableNotification -> Encoding
$ctoEncoding :: ToggleChatDefaultDisableNotification -> Encoding
toJSON :: ToggleChatDefaultDisableNotification -> Value
$ctoJSON :: ToggleChatDefaultDisableNotification -> Value
parseJSONList :: Value -> Parser [ToggleChatDefaultDisableNotification]
$cparseJSONList :: Value -> Parser [ToggleChatDefaultDisableNotification]
parseJSON :: Value -> Parser ToggleChatDefaultDisableNotification
$cparseJSON :: Value -> Parser ToggleChatDefaultDisableNotification
toEncodingList :: [SetChatClientData] -> Encoding
$ctoEncodingList :: [SetChatClientData] -> Encoding
toJSONList :: [SetChatClientData] -> Value
$ctoJSONList :: [SetChatClientData] -> Value
toEncoding :: SetChatClientData -> Encoding
$ctoEncoding :: SetChatClientData -> Encoding
toJSON :: SetChatClientData -> Value
$ctoJSON :: SetChatClientData -> Value
parseJSONList :: Value -> Parser [SetChatClientData]
$cparseJSONList :: Value -> Parser [SetChatClientData]
parseJSON :: Value -> Parser SetChatClientData
$cparseJSON :: Value -> Parser SetChatClientData
toEncodingList :: [SetChatDescription] -> Encoding
$ctoEncodingList :: [SetChatDescription] -> Encoding
toJSONList :: [SetChatDescription] -> Value
$ctoJSONList :: [SetChatDescription] -> Value
toEncoding :: SetChatDescription -> Encoding
$ctoEncoding :: SetChatDescription -> Encoding
toJSON :: SetChatDescription -> Value
$ctoJSON :: SetChatDescription -> Value
parseJSONList :: Value -> Parser [SetChatDescription]
$cparseJSONList :: Value -> Parser [SetChatDescription]
parseJSON :: Value -> Parser SetChatDescription
$cparseJSON :: Value -> Parser SetChatDescription
toEncodingList :: [SetChatDiscussionGroup] -> Encoding
$ctoEncodingList :: [SetChatDiscussionGroup] -> Encoding
toJSONList :: [SetChatDiscussionGroup] -> Value
$ctoJSONList :: [SetChatDiscussionGroup] -> Value
toEncoding :: SetChatDiscussionGroup -> Encoding
$ctoEncoding :: SetChatDiscussionGroup -> Encoding
toJSON :: SetChatDiscussionGroup -> Value
$ctoJSON :: SetChatDiscussionGroup -> Value
parseJSONList :: Value -> Parser [SetChatDiscussionGroup]
$cparseJSONList :: Value -> Parser [SetChatDiscussionGroup]
parseJSON :: Value -> Parser SetChatDiscussionGroup
$cparseJSON :: Value -> Parser SetChatDiscussionGroup
toEncodingList :: [SetChatLocation] -> Encoding
$ctoEncodingList :: [SetChatLocation] -> Encoding
toJSONList :: [SetChatLocation] -> Value
$ctoJSONList :: [SetChatLocation] -> Value
toEncoding :: SetChatLocation -> Encoding
$ctoEncoding :: SetChatLocation -> Encoding
toJSON :: SetChatLocation -> Value
$ctoJSON :: SetChatLocation -> Value
parseJSONList :: Value -> Parser [SetChatLocation]
$cparseJSONList :: Value -> Parser [SetChatLocation]
parseJSON :: Value -> Parser SetChatLocation
$cparseJSON :: Value -> Parser SetChatLocation
toEncodingList :: [SetChatSlowModeDelay] -> Encoding
$ctoEncodingList :: [SetChatSlowModeDelay] -> Encoding
toJSONList :: [SetChatSlowModeDelay] -> Value
$ctoJSONList :: [SetChatSlowModeDelay] -> Value
toEncoding :: SetChatSlowModeDelay -> Encoding
$ctoEncoding :: SetChatSlowModeDelay -> Encoding
toJSON :: SetChatSlowModeDelay -> Value
$ctoJSON :: SetChatSlowModeDelay -> Value
parseJSONList :: Value -> Parser [SetChatSlowModeDelay]
$cparseJSONList :: Value -> Parser [SetChatSlowModeDelay]
parseJSON :: Value -> Parser SetChatSlowModeDelay
$cparseJSON :: Value -> Parser SetChatSlowModeDelay
toEncodingList :: [PinChatMessage] -> Encoding
$ctoEncodingList :: [PinChatMessage] -> Encoding
toJSONList :: [PinChatMessage] -> Value
$ctoJSONList :: [PinChatMessage] -> Value
toEncoding :: PinChatMessage -> Encoding
$ctoEncoding :: PinChatMessage -> Encoding
toJSON :: PinChatMessage -> Value
$ctoJSON :: PinChatMessage -> Value
parseJSONList :: Value -> Parser [PinChatMessage]
$cparseJSONList :: Value -> Parser [PinChatMessage]
parseJSON :: Value -> Parser PinChatMessage
$cparseJSON :: Value -> Parser PinChatMessage
toEncodingList :: [UnpinChatMessage] -> Encoding
$ctoEncodingList :: [UnpinChatMessage] -> Encoding
toJSONList :: [UnpinChatMessage] -> Value
$ctoJSONList :: [UnpinChatMessage] -> Value
toEncoding :: UnpinChatMessage -> Encoding
$ctoEncoding :: UnpinChatMessage -> Encoding
toJSON :: UnpinChatMessage -> Value
$ctoJSON :: UnpinChatMessage -> Value
parseJSONList :: Value -> Parser [UnpinChatMessage]
$cparseJSONList :: Value -> Parser [UnpinChatMessage]
parseJSON :: Value -> Parser UnpinChatMessage
$cparseJSON :: Value -> Parser UnpinChatMessage
toEncodingList :: [JoinChat] -> Encoding
$ctoEncodingList :: [JoinChat] -> Encoding
toJSONList :: [JoinChat] -> Value
$ctoJSONList :: [JoinChat] -> Value
toEncoding :: JoinChat -> Encoding
$ctoEncoding :: JoinChat -> Encoding
toJSON :: JoinChat -> Value
$ctoJSON :: JoinChat -> Value
parseJSONList :: Value -> Parser [JoinChat]
$cparseJSONList :: Value -> Parser [JoinChat]
parseJSON :: Value -> Parser JoinChat
$cparseJSON :: Value -> Parser JoinChat
toEncodingList :: [LeaveChat] -> Encoding
$ctoEncodingList :: [LeaveChat] -> Encoding
toJSONList :: [LeaveChat] -> Value
$ctoJSONList :: [LeaveChat] -> Value
toEncoding :: LeaveChat -> Encoding
$ctoEncoding :: LeaveChat -> Encoding
toJSON :: LeaveChat -> Value
$ctoJSON :: LeaveChat -> Value
parseJSONList :: Value -> Parser [LeaveChat]
$cparseJSONList :: Value -> Parser [LeaveChat]
parseJSON :: Value -> Parser LeaveChat
$cparseJSON :: Value -> Parser LeaveChat
toEncodingList :: [AddChatMember] -> Encoding
$ctoEncodingList :: [AddChatMember] -> Encoding
toJSONList :: [AddChatMember] -> Value
$ctoJSONList :: [AddChatMember] -> Value
toEncoding :: AddChatMember -> Encoding
$ctoEncoding :: AddChatMember -> Encoding
toJSON :: AddChatMember -> Value
$ctoJSON :: AddChatMember -> Value
parseJSONList :: Value -> Parser [AddChatMember]
$cparseJSONList :: Value -> Parser [AddChatMember]
parseJSON :: Value -> Parser AddChatMember
$cparseJSON :: Value -> Parser AddChatMember
toEncodingList :: [AddChatMembers] -> Encoding
$ctoEncodingList :: [AddChatMembers] -> Encoding
toJSONList :: [AddChatMembers] -> Value
$ctoJSONList :: [AddChatMembers] -> Value
toEncoding :: AddChatMembers -> Encoding
$ctoEncoding :: AddChatMembers -> Encoding
toJSON :: AddChatMembers -> Value
$ctoJSON :: AddChatMembers -> Value
parseJSONList :: Value -> Parser [AddChatMembers]
$cparseJSONList :: Value -> Parser [AddChatMembers]
parseJSON :: Value -> Parser AddChatMembers
$cparseJSON :: Value -> Parser AddChatMembers
toEncodingList :: [SetChatMemberStatus] -> Encoding
$ctoEncodingList :: [SetChatMemberStatus] -> Encoding
toJSONList :: [SetChatMemberStatus] -> Value
$ctoJSONList :: [SetChatMemberStatus] -> Value
toEncoding :: SetChatMemberStatus -> Encoding
$ctoEncoding :: SetChatMemberStatus -> Encoding
toJSON :: SetChatMemberStatus -> Value
$ctoJSON :: SetChatMemberStatus -> Value
parseJSONList :: Value -> Parser [SetChatMemberStatus]
$cparseJSONList :: Value -> Parser [SetChatMemberStatus]
parseJSON :: Value -> Parser SetChatMemberStatus
$cparseJSON :: Value -> Parser SetChatMemberStatus
toEncodingList :: [CanTransferOwnership] -> Encoding
$ctoEncodingList :: [CanTransferOwnership] -> Encoding
toJSONList :: [CanTransferOwnership] -> Value
$ctoJSONList :: [CanTransferOwnership] -> Value
toEncoding :: CanTransferOwnership -> Encoding
$ctoEncoding :: CanTransferOwnership -> Encoding
toJSON :: CanTransferOwnership -> Value
$ctoJSON :: CanTransferOwnership -> Value
parseJSONList :: Value -> Parser [CanTransferOwnership]
$cparseJSONList :: Value -> Parser [CanTransferOwnership]
parseJSON :: Value -> Parser CanTransferOwnership
$cparseJSON :: Value -> Parser CanTransferOwnership
toEncodingList :: [TransferChatOwnership] -> Encoding
$ctoEncodingList :: [TransferChatOwnership] -> Encoding
toJSONList :: [TransferChatOwnership] -> Value
$ctoJSONList :: [TransferChatOwnership] -> Value
toEncoding :: TransferChatOwnership -> Encoding
$ctoEncoding :: TransferChatOwnership -> Encoding
toJSON :: TransferChatOwnership -> Value
$ctoJSON :: TransferChatOwnership -> Value
parseJSONList :: Value -> Parser [TransferChatOwnership]
$cparseJSONList :: Value -> Parser [TransferChatOwnership]
parseJSON :: Value -> Parser TransferChatOwnership
$cparseJSON :: Value -> Parser TransferChatOwnership
toEncodingList :: [GetChatMember] -> Encoding
$ctoEncodingList :: [GetChatMember] -> Encoding
toJSONList :: [GetChatMember] -> Value
$ctoJSONList :: [GetChatMember] -> Value
toEncoding :: GetChatMember -> Encoding
$ctoEncoding :: GetChatMember -> Encoding
toJSON :: GetChatMember -> Value
$ctoJSON :: GetChatMember -> Value
parseJSONList :: Value -> Parser [GetChatMember]
$cparseJSONList :: Value -> Parser [GetChatMember]
parseJSON :: Value -> Parser GetChatMember
$cparseJSON :: Value -> Parser GetChatMember
toEncodingList :: [SearchChatMembers] -> Encoding
$ctoEncodingList :: [SearchChatMembers] -> Encoding
toJSONList :: [SearchChatMembers] -> Value
$ctoJSONList :: [SearchChatMembers] -> Value
toEncoding :: SearchChatMembers -> Encoding
$ctoEncoding :: SearchChatMembers -> Encoding
toJSON :: SearchChatMembers -> Value
$ctoJSON :: SearchChatMembers -> Value
parseJSONList :: Value -> Parser [SearchChatMembers]
$cparseJSONList :: Value -> Parser [SearchChatMembers]
parseJSON :: Value -> Parser SearchChatMembers
$cparseJSON :: Value -> Parser SearchChatMembers
toEncodingList :: [GetChatAdministrators] -> Encoding
$ctoEncodingList :: [GetChatAdministrators] -> Encoding
toJSONList :: [GetChatAdministrators] -> Value
$ctoJSONList :: [GetChatAdministrators] -> Value
toEncoding :: GetChatAdministrators -> Encoding
$ctoEncoding :: GetChatAdministrators -> Encoding
toJSON :: GetChatAdministrators -> Value
$ctoJSON :: GetChatAdministrators -> Value
parseJSONList :: Value -> Parser [GetChatAdministrators]
$cparseJSONList :: Value -> Parser [GetChatAdministrators]
parseJSON :: Value -> Parser GetChatAdministrators
$cparseJSON :: Value -> Parser GetChatAdministrators
toEncodingList :: [ClearAllDraftMessages] -> Encoding
$ctoEncodingList :: [ClearAllDraftMessages] -> Encoding
toJSONList :: [ClearAllDraftMessages] -> Value
$ctoJSONList :: [ClearAllDraftMessages] -> Value
toEncoding :: ClearAllDraftMessages -> Encoding
$ctoEncoding :: ClearAllDraftMessages -> Encoding
toJSON :: ClearAllDraftMessages -> Value
$ctoJSON :: ClearAllDraftMessages -> Value
parseJSONList :: Value -> Parser [ClearAllDraftMessages]
$cparseJSONList :: Value -> Parser [ClearAllDraftMessages]
parseJSON :: Value -> Parser ClearAllDraftMessages
$cparseJSON :: Value -> Parser ClearAllDraftMessages
toEncodingList :: [GetChatNotificationSettingsExceptions] -> Encoding
$ctoEncodingList :: [GetChatNotificationSettingsExceptions] -> Encoding
toJSONList :: [GetChatNotificationSettingsExceptions] -> Value
$ctoJSONList :: [GetChatNotificationSettingsExceptions] -> Value
toEncoding :: GetChatNotificationSettingsExceptions -> Encoding
$ctoEncoding :: GetChatNotificationSettingsExceptions -> Encoding
toJSON :: GetChatNotificationSettingsExceptions -> Value
$ctoJSON :: GetChatNotificationSettingsExceptions -> Value
parseJSONList :: Value -> Parser [GetChatNotificationSettingsExceptions]
$cparseJSONList :: Value -> Parser [GetChatNotificationSettingsExceptions]
parseJSON :: Value -> Parser GetChatNotificationSettingsExceptions
$cparseJSON :: Value -> Parser GetChatNotificationSettingsExceptions
toEncodingList :: [GetScopeNotificationSettings] -> Encoding
$ctoEncodingList :: [GetScopeNotificationSettings] -> Encoding
toJSONList :: [GetScopeNotificationSettings] -> Value
$ctoJSONList :: [GetScopeNotificationSettings] -> Value
toEncoding :: GetScopeNotificationSettings -> Encoding
$ctoEncoding :: GetScopeNotificationSettings -> Encoding
toJSON :: GetScopeNotificationSettings -> Value
$ctoJSON :: GetScopeNotificationSettings -> Value
parseJSONList :: Value -> Parser [GetScopeNotificationSettings]
$cparseJSONList :: Value -> Parser [GetScopeNotificationSettings]
parseJSON :: Value -> Parser GetScopeNotificationSettings
$cparseJSON :: Value -> Parser GetScopeNotificationSettings
toEncodingList :: [SetScopeNotificationSettings] -> Encoding
$ctoEncodingList :: [SetScopeNotificationSettings] -> Encoding
toJSONList :: [SetScopeNotificationSettings] -> Value
$ctoJSONList :: [SetScopeNotificationSettings] -> Value
toEncoding :: SetScopeNotificationSettings -> Encoding
$ctoEncoding :: SetScopeNotificationSettings -> Encoding
toJSON :: SetScopeNotificationSettings -> Value
$ctoJSON :: SetScopeNotificationSettings -> Value
parseJSONList :: Value -> Parser [SetScopeNotificationSettings]
$cparseJSONList :: Value -> Parser [SetScopeNotificationSettings]
parseJSON :: Value -> Parser SetScopeNotificationSettings
$cparseJSON :: Value -> Parser SetScopeNotificationSettings
toEncodingList :: [ResetAllNotificationSettings] -> Encoding
$ctoEncodingList :: [ResetAllNotificationSettings] -> Encoding
toJSONList :: [ResetAllNotificationSettings] -> Value
$ctoJSONList :: [ResetAllNotificationSettings] -> Value
toEncoding :: ResetAllNotificationSettings -> Encoding
$ctoEncoding :: ResetAllNotificationSettings -> Encoding
toJSON :: ResetAllNotificationSettings -> Value
$ctoJSON :: ResetAllNotificationSettings -> Value
parseJSONList :: Value -> Parser [ResetAllNotificationSettings]
$cparseJSONList :: Value -> Parser [ResetAllNotificationSettings]
parseJSON :: Value -> Parser ResetAllNotificationSettings
$cparseJSON :: Value -> Parser ResetAllNotificationSettings
toEncodingList :: [SetPinnedChats] -> Encoding
$ctoEncodingList :: [SetPinnedChats] -> Encoding
toJSONList :: [SetPinnedChats] -> Value
$ctoJSONList :: [SetPinnedChats] -> Value
toEncoding :: SetPinnedChats -> Encoding
$ctoEncoding :: SetPinnedChats -> Encoding
toJSON :: SetPinnedChats -> Value
$ctoJSON :: SetPinnedChats -> Value
parseJSONList :: Value -> Parser [SetPinnedChats]
$cparseJSONList :: Value -> Parser [SetPinnedChats]
parseJSON :: Value -> Parser SetPinnedChats
$cparseJSON :: Value -> Parser SetPinnedChats
toEncodingList :: [DownloadFile] -> Encoding
$ctoEncodingList :: [DownloadFile] -> Encoding
toJSONList :: [DownloadFile] -> Value
$ctoJSONList :: [DownloadFile] -> Value
toEncoding :: DownloadFile -> Encoding
$ctoEncoding :: DownloadFile -> Encoding
toJSON :: DownloadFile -> Value
$ctoJSON :: DownloadFile -> Value
parseJSONList :: Value -> Parser [DownloadFile]
$cparseJSONList :: Value -> Parser [DownloadFile]
parseJSON :: Value -> Parser DownloadFile
$cparseJSON :: Value -> Parser DownloadFile
toEncodingList :: [GetFileDownloadedPrefixSize] -> Encoding
$ctoEncodingList :: [GetFileDownloadedPrefixSize] -> Encoding
toJSONList :: [GetFileDownloadedPrefixSize] -> Value
$ctoJSONList :: [GetFileDownloadedPrefixSize] -> Value
toEncoding :: GetFileDownloadedPrefixSize -> Encoding
$ctoEncoding :: GetFileDownloadedPrefixSize -> Encoding
toJSON :: GetFileDownloadedPrefixSize -> Value
$ctoJSON :: GetFileDownloadedPrefixSize -> Value
parseJSONList :: Value -> Parser [GetFileDownloadedPrefixSize]
$cparseJSONList :: Value -> Parser [GetFileDownloadedPrefixSize]
parseJSON :: Value -> Parser GetFileDownloadedPrefixSize
$cparseJSON :: Value -> Parser GetFileDownloadedPrefixSize
toEncodingList :: [CancelDownloadFile] -> Encoding
$ctoEncodingList :: [CancelDownloadFile] -> Encoding
toJSONList :: [CancelDownloadFile] -> Value
$ctoJSONList :: [CancelDownloadFile] -> Value
toEncoding :: CancelDownloadFile -> Encoding
$ctoEncoding :: CancelDownloadFile -> Encoding
toJSON :: CancelDownloadFile -> Value
$ctoJSON :: CancelDownloadFile -> Value
parseJSONList :: Value -> Parser [CancelDownloadFile]
$cparseJSONList :: Value -> Parser [CancelDownloadFile]
parseJSON :: Value -> Parser CancelDownloadFile
$cparseJSON :: Value -> Parser CancelDownloadFile
toEncodingList :: [UploadFile] -> Encoding
$ctoEncodingList :: [UploadFile] -> Encoding
toJSONList :: [UploadFile] -> Value
$ctoJSONList :: [UploadFile] -> Value
toEncoding :: UploadFile -> Encoding
$ctoEncoding :: UploadFile -> Encoding
toJSON :: UploadFile -> Value
$ctoJSON :: UploadFile -> Value
parseJSONList :: Value -> Parser [UploadFile]
$cparseJSONList :: Value -> Parser [UploadFile]
parseJSON :: Value -> Parser UploadFile
$cparseJSON :: Value -> Parser UploadFile
toEncodingList :: [CancelUploadFile] -> Encoding
$ctoEncodingList :: [CancelUploadFile] -> Encoding
toJSONList :: [CancelUploadFile] -> Value
$ctoJSONList :: [CancelUploadFile] -> Value
toEncoding :: CancelUploadFile -> Encoding
$ctoEncoding :: CancelUploadFile -> Encoding
toJSON :: CancelUploadFile -> Value
$ctoJSON :: CancelUploadFile -> Value
parseJSONList :: Value -> Parser [CancelUploadFile]
$cparseJSONList :: Value -> Parser [CancelUploadFile]
parseJSON :: Value -> Parser CancelUploadFile
$cparseJSON :: Value -> Parser CancelUploadFile
toEncodingList :: [WriteGeneratedFilePart] -> Encoding
$ctoEncodingList :: [WriteGeneratedFilePart] -> Encoding
toJSONList :: [WriteGeneratedFilePart] -> Value
$ctoJSONList :: [WriteGeneratedFilePart] -> Value
toEncoding :: WriteGeneratedFilePart -> Encoding
$ctoEncoding :: WriteGeneratedFilePart -> Encoding
toJSON :: WriteGeneratedFilePart -> Value
$ctoJSON :: WriteGeneratedFilePart -> Value
parseJSONList :: Value -> Parser [WriteGeneratedFilePart]
$cparseJSONList :: Value -> Parser [WriteGeneratedFilePart]
parseJSON :: Value -> Parser WriteGeneratedFilePart
$cparseJSON :: Value -> Parser WriteGeneratedFilePart
toEncodingList :: [SetFileGenerationProgress] -> Encoding
$ctoEncodingList :: [SetFileGenerationProgress] -> Encoding
toJSONList :: [SetFileGenerationProgress] -> Value
$ctoJSONList :: [SetFileGenerationProgress] -> Value
toEncoding :: SetFileGenerationProgress -> Encoding
$ctoEncoding :: SetFileGenerationProgress -> Encoding
toJSON :: SetFileGenerationProgress -> Value
$ctoJSON :: SetFileGenerationProgress -> Value
parseJSONList :: Value -> Parser [SetFileGenerationProgress]
$cparseJSONList :: Value -> Parser [SetFileGenerationProgress]
parseJSON :: Value -> Parser SetFileGenerationProgress
$cparseJSON :: Value -> Parser SetFileGenerationProgress
toEncodingList :: [FinishFileGeneration] -> Encoding
$ctoEncodingList :: [FinishFileGeneration] -> Encoding
toJSONList :: [FinishFileGeneration] -> Value
$ctoJSONList :: [FinishFileGeneration] -> Value
toEncoding :: FinishFileGeneration -> Encoding
$ctoEncoding :: FinishFileGeneration -> Encoding
toJSON :: FinishFileGeneration -> Value
$ctoJSON :: FinishFileGeneration -> Value
parseJSONList :: Value -> Parser [FinishFileGeneration]
$cparseJSONList :: Value -> Parser [FinishFileGeneration]
parseJSON :: Value -> Parser FinishFileGeneration
$cparseJSON :: Value -> Parser FinishFileGeneration
toEncodingList :: [ReadFilePart] -> Encoding
$ctoEncodingList :: [ReadFilePart] -> Encoding
toJSONList :: [ReadFilePart] -> Value
$ctoJSONList :: [ReadFilePart] -> Value
toEncoding :: ReadFilePart -> Encoding
$ctoEncoding :: ReadFilePart -> Encoding
toJSON :: ReadFilePart -> Value
$ctoJSON :: ReadFilePart -> Value
parseJSONList :: Value -> Parser [ReadFilePart]
$cparseJSONList :: Value -> Parser [ReadFilePart]
parseJSON :: Value -> Parser ReadFilePart
$cparseJSON :: Value -> Parser ReadFilePart
toEncodingList :: [DeleteFile] -> Encoding
$ctoEncodingList :: [DeleteFile] -> Encoding
toJSONList :: [DeleteFile] -> Value
$ctoJSONList :: [DeleteFile] -> Value
toEncoding :: DeleteFile -> Encoding
$ctoEncoding :: DeleteFile -> Encoding
toJSON :: DeleteFile -> Value
$ctoJSON :: DeleteFile -> Value
parseJSONList :: Value -> Parser [DeleteFile]
$cparseJSONList :: Value -> Parser [DeleteFile]
parseJSON :: Value -> Parser DeleteFile
$cparseJSON :: Value -> Parser DeleteFile
toEncodingList :: [GenerateChatInviteLink] -> Encoding
$ctoEncodingList :: [GenerateChatInviteLink] -> Encoding
toJSONList :: [GenerateChatInviteLink] -> Value
$ctoJSONList :: [GenerateChatInviteLink] -> Value
toEncoding :: GenerateChatInviteLink -> Encoding
$ctoEncoding :: GenerateChatInviteLink -> Encoding
toJSON :: GenerateChatInviteLink -> Value
$ctoJSON :: GenerateChatInviteLink -> Value
parseJSONList :: Value -> Parser [GenerateChatInviteLink]
$cparseJSONList :: Value -> Parser [GenerateChatInviteLink]
parseJSON :: Value -> Parser GenerateChatInviteLink
$cparseJSON :: Value -> Parser GenerateChatInviteLink
toEncodingList :: [CheckChatInviteLink] -> Encoding
$ctoEncodingList :: [CheckChatInviteLink] -> Encoding
toJSONList :: [CheckChatInviteLink] -> Value
$ctoJSONList :: [CheckChatInviteLink] -> Value
toEncoding :: CheckChatInviteLink -> Encoding
$ctoEncoding :: CheckChatInviteLink -> Encoding
toJSON :: CheckChatInviteLink -> Value
$ctoJSON :: CheckChatInviteLink -> Value
parseJSONList :: Value -> Parser [CheckChatInviteLink]
$cparseJSONList :: Value -> Parser [CheckChatInviteLink]
parseJSON :: Value -> Parser CheckChatInviteLink
$cparseJSON :: Value -> Parser CheckChatInviteLink
toEncodingList :: [JoinChatByInviteLink] -> Encoding
$ctoEncodingList :: [JoinChatByInviteLink] -> Encoding
toJSONList :: [JoinChatByInviteLink] -> Value
$ctoJSONList :: [JoinChatByInviteLink] -> Value
toEncoding :: JoinChatByInviteLink -> Encoding
$ctoEncoding :: JoinChatByInviteLink -> Encoding
toJSON :: JoinChatByInviteLink -> Value
$ctoJSON :: JoinChatByInviteLink -> Value
parseJSONList :: Value -> Parser [JoinChatByInviteLink]
$cparseJSONList :: Value -> Parser [JoinChatByInviteLink]
parseJSON :: Value -> Parser JoinChatByInviteLink
$cparseJSON :: Value -> Parser JoinChatByInviteLink
toEncodingList :: [CreateCall] -> Encoding
$ctoEncodingList :: [CreateCall] -> Encoding
toJSONList :: [CreateCall] -> Value
$ctoJSONList :: [CreateCall] -> Value
toEncoding :: CreateCall -> Encoding
$ctoEncoding :: CreateCall -> Encoding
toJSON :: CreateCall -> Value
$ctoJSON :: CreateCall -> Value
parseJSONList :: Value -> Parser [CreateCall]
$cparseJSONList :: Value -> Parser [CreateCall]
parseJSON :: Value -> Parser CreateCall
$cparseJSON :: Value -> Parser CreateCall
toEncodingList :: [AcceptCall] -> Encoding
$ctoEncodingList :: [AcceptCall] -> Encoding
toJSONList :: [AcceptCall] -> Value
$ctoJSONList :: [AcceptCall] -> Value
toEncoding :: AcceptCall -> Encoding
$ctoEncoding :: AcceptCall -> Encoding
toJSON :: AcceptCall -> Value
$ctoJSON :: AcceptCall -> Value
parseJSONList :: Value -> Parser [AcceptCall]
$cparseJSONList :: Value -> Parser [AcceptCall]
parseJSON :: Value -> Parser AcceptCall
$cparseJSON :: Value -> Parser AcceptCall
toEncodingList :: [DiscardCall] -> Encoding
$ctoEncodingList :: [DiscardCall] -> Encoding
toJSONList :: [DiscardCall] -> Value
$ctoJSONList :: [DiscardCall] -> Value
toEncoding :: DiscardCall -> Encoding
$ctoEncoding :: DiscardCall -> Encoding
toJSON :: DiscardCall -> Value
$ctoJSON :: DiscardCall -> Value
parseJSONList :: Value -> Parser [DiscardCall]
$cparseJSONList :: Value -> Parser [DiscardCall]
parseJSON :: Value -> Parser DiscardCall
$cparseJSON :: Value -> Parser DiscardCall
toEncodingList :: [SendCallRating] -> Encoding
$ctoEncodingList :: [SendCallRating] -> Encoding
toJSONList :: [SendCallRating] -> Value
$ctoJSONList :: [SendCallRating] -> Value
toEncoding :: SendCallRating -> Encoding
$ctoEncoding :: SendCallRating -> Encoding
toJSON :: SendCallRating -> Value
$ctoJSON :: SendCallRating -> Value
parseJSONList :: Value -> Parser [SendCallRating]
$cparseJSONList :: Value -> Parser [SendCallRating]
parseJSON :: Value -> Parser SendCallRating
$cparseJSON :: Value -> Parser SendCallRating
toEncodingList :: [SendCallDebugInformation] -> Encoding
$ctoEncodingList :: [SendCallDebugInformation] -> Encoding
toJSONList :: [SendCallDebugInformation] -> Value
$ctoJSONList :: [SendCallDebugInformation] -> Value
toEncoding :: SendCallDebugInformation -> Encoding
$ctoEncoding :: SendCallDebugInformation -> Encoding
toJSON :: SendCallDebugInformation -> Value
$ctoJSON :: SendCallDebugInformation -> Value
parseJSONList :: Value -> Parser [SendCallDebugInformation]
$cparseJSONList :: Value -> Parser [SendCallDebugInformation]
parseJSON :: Value -> Parser SendCallDebugInformation
$cparseJSON :: Value -> Parser SendCallDebugInformation
toEncodingList :: [BlockUser] -> Encoding
$ctoEncodingList :: [BlockUser] -> Encoding
toJSONList :: [BlockUser] -> Value
$ctoJSONList :: [BlockUser] -> Value
toEncoding :: BlockUser -> Encoding
$ctoEncoding :: BlockUser -> Encoding
toJSON :: BlockUser -> Value
$ctoJSON :: BlockUser -> Value
parseJSONList :: Value -> Parser [BlockUser]
$cparseJSONList :: Value -> Parser [BlockUser]
parseJSON :: Value -> Parser BlockUser
$cparseJSON :: Value -> Parser BlockUser
toEncodingList :: [UnblockUser] -> Encoding
$ctoEncodingList :: [UnblockUser] -> Encoding
toJSONList :: [UnblockUser] -> Value
$ctoJSONList :: [UnblockUser] -> Value
toEncoding :: UnblockUser -> Encoding
$ctoEncoding :: UnblockUser -> Encoding
toJSON :: UnblockUser -> Value
$ctoJSON :: UnblockUser -> Value
parseJSONList :: Value -> Parser [UnblockUser]
$cparseJSONList :: Value -> Parser [UnblockUser]
parseJSON :: Value -> Parser UnblockUser
$cparseJSON :: Value -> Parser UnblockUser
toEncodingList :: [GetBlockedUsers] -> Encoding
$ctoEncodingList :: [GetBlockedUsers] -> Encoding
toJSONList :: [GetBlockedUsers] -> Value
$ctoJSONList :: [GetBlockedUsers] -> Value
toEncoding :: GetBlockedUsers -> Encoding
$ctoEncoding :: GetBlockedUsers -> Encoding
toJSON :: GetBlockedUsers -> Value
$ctoJSON :: GetBlockedUsers -> Value
parseJSONList :: Value -> Parser [GetBlockedUsers]
$cparseJSONList :: Value -> Parser [GetBlockedUsers]
parseJSON :: Value -> Parser GetBlockedUsers
$cparseJSON :: Value -> Parser GetBlockedUsers
toEncodingList :: [AddContact] -> Encoding
$ctoEncodingList :: [AddContact] -> Encoding
toJSONList :: [AddContact] -> Value
$ctoJSONList :: [AddContact] -> Value
toEncoding :: AddContact -> Encoding
$ctoEncoding :: AddContact -> Encoding
toJSON :: AddContact -> Value
$ctoJSON :: AddContact -> Value
parseJSONList :: Value -> Parser [AddContact]
$cparseJSONList :: Value -> Parser [AddContact]
parseJSON :: Value -> Parser AddContact
$cparseJSON :: Value -> Parser AddContact
toEncodingList :: [ImportContacts] -> Encoding
$ctoEncodingList :: [ImportContacts] -> Encoding
toJSONList :: [ImportContacts] -> Value
$ctoJSONList :: [ImportContacts] -> Value
toEncoding :: ImportContacts -> Encoding
$ctoEncoding :: ImportContacts -> Encoding
toJSON :: ImportContacts -> Value
$ctoJSON :: ImportContacts -> Value
parseJSONList :: Value -> Parser [ImportContacts]
$cparseJSONList :: Value -> Parser [ImportContacts]
parseJSON :: Value -> Parser ImportContacts
$cparseJSON :: Value -> Parser ImportContacts
toEncodingList :: [GetContacts] -> Encoding
$ctoEncodingList :: [GetContacts] -> Encoding
toJSONList :: [GetContacts] -> Value
$ctoJSONList :: [GetContacts] -> Value
toEncoding :: GetContacts -> Encoding
$ctoEncoding :: GetContacts -> Encoding
toJSON :: GetContacts -> Value
$ctoJSON :: GetContacts -> Value
parseJSONList :: Value -> Parser [GetContacts]
$cparseJSONList :: Value -> Parser [GetContacts]
parseJSON :: Value -> Parser GetContacts
$cparseJSON :: Value -> Parser GetContacts
toEncodingList :: [SearchContacts] -> Encoding
$ctoEncodingList :: [SearchContacts] -> Encoding
toJSONList :: [SearchContacts] -> Value
$ctoJSONList :: [SearchContacts] -> Value
toEncoding :: SearchContacts -> Encoding
$ctoEncoding :: SearchContacts -> Encoding
toJSON :: SearchContacts -> Value
$ctoJSON :: SearchContacts -> Value
parseJSONList :: Value -> Parser [SearchContacts]
$cparseJSONList :: Value -> Parser [SearchContacts]
parseJSON :: Value -> Parser SearchContacts
$cparseJSON :: Value -> Parser SearchContacts
toEncodingList :: [RemoveContacts] -> Encoding
$ctoEncodingList :: [RemoveContacts] -> Encoding
toJSONList :: [RemoveContacts] -> Value
$ctoJSONList :: [RemoveContacts] -> Value
toEncoding :: RemoveContacts -> Encoding
$ctoEncoding :: RemoveContacts -> Encoding
toJSON :: RemoveContacts -> Value
$ctoJSON :: RemoveContacts -> Value
parseJSONList :: Value -> Parser [RemoveContacts]
$cparseJSONList :: Value -> Parser [RemoveContacts]
parseJSON :: Value -> Parser RemoveContacts
$cparseJSON :: Value -> Parser RemoveContacts
toEncodingList :: [GetImportedContactCount] -> Encoding
$ctoEncodingList :: [GetImportedContactCount] -> Encoding
toJSONList :: [GetImportedContactCount] -> Value
$ctoJSONList :: [GetImportedContactCount] -> Value
toEncoding :: GetImportedContactCount -> Encoding
$ctoEncoding :: GetImportedContactCount -> Encoding
toJSON :: GetImportedContactCount -> Value
$ctoJSON :: GetImportedContactCount -> Value
parseJSONList :: Value -> Parser [GetImportedContactCount]
$cparseJSONList :: Value -> Parser [GetImportedContactCount]
parseJSON :: Value -> Parser GetImportedContactCount
$cparseJSON :: Value -> Parser GetImportedContactCount
toEncodingList :: [ChangeImportedContacts] -> Encoding
$ctoEncodingList :: [ChangeImportedContacts] -> Encoding
toJSONList :: [ChangeImportedContacts] -> Value
$ctoJSONList :: [ChangeImportedContacts] -> Value
toEncoding :: ChangeImportedContacts -> Encoding
$ctoEncoding :: ChangeImportedContacts -> Encoding
toJSON :: ChangeImportedContacts -> Value
$ctoJSON :: ChangeImportedContacts -> Value
parseJSONList :: Value -> Parser [ChangeImportedContacts]
$cparseJSONList :: Value -> Parser [ChangeImportedContacts]
parseJSON :: Value -> Parser ChangeImportedContacts
$cparseJSON :: Value -> Parser ChangeImportedContacts
toEncodingList :: [ClearImportedContacts] -> Encoding
$ctoEncodingList :: [ClearImportedContacts] -> Encoding
toJSONList :: [ClearImportedContacts] -> Value
$ctoJSONList :: [ClearImportedContacts] -> Value
toEncoding :: ClearImportedContacts -> Encoding
$ctoEncoding :: ClearImportedContacts -> Encoding
toJSON :: ClearImportedContacts -> Value
$ctoJSON :: ClearImportedContacts -> Value
parseJSONList :: Value -> Parser [ClearImportedContacts]
$cparseJSONList :: Value -> Parser [ClearImportedContacts]
parseJSON :: Value -> Parser ClearImportedContacts
$cparseJSON :: Value -> Parser ClearImportedContacts
toEncodingList :: [SharePhoneNumber] -> Encoding
$ctoEncodingList :: [SharePhoneNumber] -> Encoding
toJSONList :: [SharePhoneNumber] -> Value
$ctoJSONList :: [SharePhoneNumber] -> Value
toEncoding :: SharePhoneNumber -> Encoding
$ctoEncoding :: SharePhoneNumber -> Encoding
toJSON :: SharePhoneNumber -> Value
$ctoJSON :: SharePhoneNumber -> Value
parseJSONList :: Value -> Parser [SharePhoneNumber]
$cparseJSONList :: Value -> Parser [SharePhoneNumber]
parseJSON :: Value -> Parser SharePhoneNumber
$cparseJSON :: Value -> Parser SharePhoneNumber
toEncodingList :: [GetUserProfilePhotos] -> Encoding
$ctoEncodingList :: [GetUserProfilePhotos] -> Encoding
toJSONList :: [GetUserProfilePhotos] -> Value
$ctoJSONList :: [GetUserProfilePhotos] -> Value
toEncoding :: GetUserProfilePhotos -> Encoding
$ctoEncoding :: GetUserProfilePhotos -> Encoding
toJSON :: GetUserProfilePhotos -> Value
$ctoJSON :: GetUserProfilePhotos -> Value
parseJSONList :: Value -> Parser [GetUserProfilePhotos]
$cparseJSONList :: Value -> Parser [GetUserProfilePhotos]
parseJSON :: Value -> Parser GetUserProfilePhotos
$cparseJSON :: Value -> Parser GetUserProfilePhotos
toEncodingList :: [GetStickers] -> Encoding
$ctoEncodingList :: [GetStickers] -> Encoding
toJSONList :: [GetStickers] -> Value
$ctoJSONList :: [GetStickers] -> Value
toEncoding :: GetStickers -> Encoding
$ctoEncoding :: GetStickers -> Encoding
toJSON :: GetStickers -> Value
$ctoJSON :: GetStickers -> Value
parseJSONList :: Value -> Parser [GetStickers]
$cparseJSONList :: Value -> Parser [GetStickers]
parseJSON :: Value -> Parser GetStickers
$cparseJSON :: Value -> Parser GetStickers
toEncodingList :: [SearchStickers] -> Encoding
$ctoEncodingList :: [SearchStickers] -> Encoding
toJSONList :: [SearchStickers] -> Value
$ctoJSONList :: [SearchStickers] -> Value
toEncoding :: SearchStickers -> Encoding
$ctoEncoding :: SearchStickers -> Encoding
toJSON :: SearchStickers -> Value
$ctoJSON :: SearchStickers -> Value
parseJSONList :: Value -> Parser [SearchStickers]
$cparseJSONList :: Value -> Parser [SearchStickers]
parseJSON :: Value -> Parser SearchStickers
$cparseJSON :: Value -> Parser SearchStickers
toEncodingList :: [GetInstalledStickerSets] -> Encoding
$ctoEncodingList :: [GetInstalledStickerSets] -> Encoding
toJSONList :: [GetInstalledStickerSets] -> Value
$ctoJSONList :: [GetInstalledStickerSets] -> Value
toEncoding :: GetInstalledStickerSets -> Encoding
$ctoEncoding :: GetInstalledStickerSets -> Encoding
toJSON :: GetInstalledStickerSets -> Value
$ctoJSON :: GetInstalledStickerSets -> Value
parseJSONList :: Value -> Parser [GetInstalledStickerSets]
$cparseJSONList :: Value -> Parser [GetInstalledStickerSets]
parseJSON :: Value -> Parser GetInstalledStickerSets
$cparseJSON :: Value -> Parser GetInstalledStickerSets
toEncodingList :: [GetArchivedStickerSets] -> Encoding
$ctoEncodingList :: [GetArchivedStickerSets] -> Encoding
toJSONList :: [GetArchivedStickerSets] -> Value
$ctoJSONList :: [GetArchivedStickerSets] -> Value
toEncoding :: GetArchivedStickerSets -> Encoding
$ctoEncoding :: GetArchivedStickerSets -> Encoding
toJSON :: GetArchivedStickerSets -> Value
$ctoJSON :: GetArchivedStickerSets -> Value
parseJSONList :: Value -> Parser [GetArchivedStickerSets]
$cparseJSONList :: Value -> Parser [GetArchivedStickerSets]
parseJSON :: Value -> Parser GetArchivedStickerSets
$cparseJSON :: Value -> Parser GetArchivedStickerSets
toEncodingList :: [GetTrendingStickerSets] -> Encoding
$ctoEncodingList :: [GetTrendingStickerSets] -> Encoding
toJSONList :: [GetTrendingStickerSets] -> Value
$ctoJSONList :: [GetTrendingStickerSets] -> Value
toEncoding :: GetTrendingStickerSets -> Encoding
$ctoEncoding :: GetTrendingStickerSets -> Encoding
toJSON :: GetTrendingStickerSets -> Value
$ctoJSON :: GetTrendingStickerSets -> Value
parseJSONList :: Value -> Parser [GetTrendingStickerSets]
$cparseJSONList :: Value -> Parser [GetTrendingStickerSets]
parseJSON :: Value -> Parser GetTrendingStickerSets
$cparseJSON :: Value -> Parser GetTrendingStickerSets
toEncodingList :: [GetAttachedStickerSets] -> Encoding
$ctoEncodingList :: [GetAttachedStickerSets] -> Encoding
toJSONList :: [GetAttachedStickerSets] -> Value
$ctoJSONList :: [GetAttachedStickerSets] -> Value
toEncoding :: GetAttachedStickerSets -> Encoding
$ctoEncoding :: GetAttachedStickerSets -> Encoding
toJSON :: GetAttachedStickerSets -> Value
$ctoJSON :: GetAttachedStickerSets -> Value
parseJSONList :: Value -> Parser [GetAttachedStickerSets]
$cparseJSONList :: Value -> Parser [GetAttachedStickerSets]
parseJSON :: Value -> Parser GetAttachedStickerSets
$cparseJSON :: Value -> Parser GetAttachedStickerSets
toEncodingList :: [GetStickerSet] -> Encoding
$ctoEncodingList :: [GetStickerSet] -> Encoding
toJSONList :: [GetStickerSet] -> Value
$ctoJSONList :: [GetStickerSet] -> Value
toEncoding :: GetStickerSet -> Encoding
$ctoEncoding :: GetStickerSet -> Encoding
toJSON :: GetStickerSet -> Value
$ctoJSON :: GetStickerSet -> Value
parseJSONList :: Value -> Parser [GetStickerSet]
$cparseJSONList :: Value -> Parser [GetStickerSet]
parseJSON :: Value -> Parser GetStickerSet
$cparseJSON :: Value -> Parser GetStickerSet
toEncodingList :: [SearchStickerSet] -> Encoding
$ctoEncodingList :: [SearchStickerSet] -> Encoding
toJSONList :: [SearchStickerSet] -> Value
$ctoJSONList :: [SearchStickerSet] -> Value
toEncoding :: SearchStickerSet -> Encoding
$ctoEncoding :: SearchStickerSet -> Encoding
toJSON :: SearchStickerSet -> Value
$ctoJSON :: SearchStickerSet -> Value
parseJSONList :: Value -> Parser [SearchStickerSet]
$cparseJSONList :: Value -> Parser [SearchStickerSet]
parseJSON :: Value -> Parser SearchStickerSet
$cparseJSON :: Value -> Parser SearchStickerSet
toEncodingList :: [SearchInstalledStickerSets] -> Encoding
$ctoEncodingList :: [SearchInstalledStickerSets] -> Encoding
toJSONList :: [SearchInstalledStickerSets] -> Value
$ctoJSONList :: [SearchInstalledStickerSets] -> Value
toEncoding :: SearchInstalledStickerSets -> Encoding
$ctoEncoding :: SearchInstalledStickerSets -> Encoding
toJSON :: SearchInstalledStickerSets -> Value
$ctoJSON :: SearchInstalledStickerSets -> Value
parseJSONList :: Value -> Parser [SearchInstalledStickerSets]
$cparseJSONList :: Value -> Parser [SearchInstalledStickerSets]
parseJSON :: Value -> Parser SearchInstalledStickerSets
$cparseJSON :: Value -> Parser SearchInstalledStickerSets
toEncodingList :: [SearchStickerSets] -> Encoding
$ctoEncodingList :: [SearchStickerSets] -> Encoding
toJSONList :: [SearchStickerSets] -> Value
$ctoJSONList :: [SearchStickerSets] -> Value
toEncoding :: SearchStickerSets -> Encoding
$ctoEncoding :: SearchStickerSets -> Encoding
toJSON :: SearchStickerSets -> Value
$ctoJSON :: SearchStickerSets -> Value
parseJSONList :: Value -> Parser [SearchStickerSets]
$cparseJSONList :: Value -> Parser [SearchStickerSets]
parseJSON :: Value -> Parser SearchStickerSets
$cparseJSON :: Value -> Parser SearchStickerSets
toEncodingList :: [ChangeStickerSet] -> Encoding
$ctoEncodingList :: [ChangeStickerSet] -> Encoding
toJSONList :: [ChangeStickerSet] -> Value
$ctoJSONList :: [ChangeStickerSet] -> Value
toEncoding :: ChangeStickerSet -> Encoding
$ctoEncoding :: ChangeStickerSet -> Encoding
toJSON :: ChangeStickerSet -> Value
$ctoJSON :: ChangeStickerSet -> Value
parseJSONList :: Value -> Parser [ChangeStickerSet]
$cparseJSONList :: Value -> Parser [ChangeStickerSet]
parseJSON :: Value -> Parser ChangeStickerSet
$cparseJSON :: Value -> Parser ChangeStickerSet
toEncodingList :: [ViewTrendingStickerSets] -> Encoding
$ctoEncodingList :: [ViewTrendingStickerSets] -> Encoding
toJSONList :: [ViewTrendingStickerSets] -> Value
$ctoJSONList :: [ViewTrendingStickerSets] -> Value
toEncoding :: ViewTrendingStickerSets -> Encoding
$ctoEncoding :: ViewTrendingStickerSets -> Encoding
toJSON :: ViewTrendingStickerSets -> Value
$ctoJSON :: ViewTrendingStickerSets -> Value
parseJSONList :: Value -> Parser [ViewTrendingStickerSets]
$cparseJSONList :: Value -> Parser [ViewTrendingStickerSets]
parseJSON :: Value -> Parser ViewTrendingStickerSets
$cparseJSON :: Value -> Parser ViewTrendingStickerSets
toEncodingList :: [ReorderInstalledStickerSets] -> Encoding
$ctoEncodingList :: [ReorderInstalledStickerSets] -> Encoding
toJSONList :: [ReorderInstalledStickerSets] -> Value
$ctoJSONList :: [ReorderInstalledStickerSets] -> Value
toEncoding :: ReorderInstalledStickerSets -> Encoding
$ctoEncoding :: ReorderInstalledStickerSets -> Encoding
toJSON :: ReorderInstalledStickerSets -> Value
$ctoJSON :: ReorderInstalledStickerSets -> Value
parseJSONList :: Value -> Parser [ReorderInstalledStickerSets]
$cparseJSONList :: Value -> Parser [ReorderInstalledStickerSets]
parseJSON :: Value -> Parser ReorderInstalledStickerSets
$cparseJSON :: Value -> Parser ReorderInstalledStickerSets
toEncodingList :: [GetRecentStickers] -> Encoding
$ctoEncodingList :: [GetRecentStickers] -> Encoding
toJSONList :: [GetRecentStickers] -> Value
$ctoJSONList :: [GetRecentStickers] -> Value
toEncoding :: GetRecentStickers -> Encoding
$ctoEncoding :: GetRecentStickers -> Encoding
toJSON :: GetRecentStickers -> Value
$ctoJSON :: GetRecentStickers -> Value
parseJSONList :: Value -> Parser [GetRecentStickers]
$cparseJSONList :: Value -> Parser [GetRecentStickers]
parseJSON :: Value -> Parser GetRecentStickers
$cparseJSON :: Value -> Parser GetRecentStickers
toEncodingList :: [AddRecentSticker] -> Encoding
$ctoEncodingList :: [AddRecentSticker] -> Encoding
toJSONList :: [AddRecentSticker] -> Value
$ctoJSONList :: [AddRecentSticker] -> Value
toEncoding :: AddRecentSticker -> Encoding
$ctoEncoding :: AddRecentSticker -> Encoding
toJSON :: AddRecentSticker -> Value
$ctoJSON :: AddRecentSticker -> Value
parseJSONList :: Value -> Parser [AddRecentSticker]
$cparseJSONList :: Value -> Parser [AddRecentSticker]
parseJSON :: Value -> Parser AddRecentSticker
$cparseJSON :: Value -> Parser AddRecentSticker
toEncodingList :: [RemoveRecentSticker] -> Encoding
$ctoEncodingList :: [RemoveRecentSticker] -> Encoding
toJSONList :: [RemoveRecentSticker] -> Value
$ctoJSONList :: [RemoveRecentSticker] -> Value
toEncoding :: RemoveRecentSticker -> Encoding
$ctoEncoding :: RemoveRecentSticker -> Encoding
toJSON :: RemoveRecentSticker -> Value
$ctoJSON :: RemoveRecentSticker -> Value
parseJSONList :: Value -> Parser [RemoveRecentSticker]
$cparseJSONList :: Value -> Parser [RemoveRecentSticker]
parseJSON :: Value -> Parser RemoveRecentSticker
$cparseJSON :: Value -> Parser RemoveRecentSticker
toEncodingList :: [ClearRecentStickers] -> Encoding
$ctoEncodingList :: [ClearRecentStickers] -> Encoding
toJSONList :: [ClearRecentStickers] -> Value
$ctoJSONList :: [ClearRecentStickers] -> Value
toEncoding :: ClearRecentStickers -> Encoding
$ctoEncoding :: ClearRecentStickers -> Encoding
toJSON :: ClearRecentStickers -> Value
$ctoJSON :: ClearRecentStickers -> Value
parseJSONList :: Value -> Parser [ClearRecentStickers]
$cparseJSONList :: Value -> Parser [ClearRecentStickers]
parseJSON :: Value -> Parser ClearRecentStickers
$cparseJSON :: Value -> Parser ClearRecentStickers
toEncodingList :: [GetFavoriteStickers] -> Encoding
$ctoEncodingList :: [GetFavoriteStickers] -> Encoding
toJSONList :: [GetFavoriteStickers] -> Value
$ctoJSONList :: [GetFavoriteStickers] -> Value
toEncoding :: GetFavoriteStickers -> Encoding
$ctoEncoding :: GetFavoriteStickers -> Encoding
toJSON :: GetFavoriteStickers -> Value
$ctoJSON :: GetFavoriteStickers -> Value
parseJSONList :: Value -> Parser [GetFavoriteStickers]
$cparseJSONList :: Value -> Parser [GetFavoriteStickers]
parseJSON :: Value -> Parser GetFavoriteStickers
$cparseJSON :: Value -> Parser GetFavoriteStickers
toEncodingList :: [AddFavoriteSticker] -> Encoding
$ctoEncodingList :: [AddFavoriteSticker] -> Encoding
toJSONList :: [AddFavoriteSticker] -> Value
$ctoJSONList :: [AddFavoriteSticker] -> Value
toEncoding :: AddFavoriteSticker -> Encoding
$ctoEncoding :: AddFavoriteSticker -> Encoding
toJSON :: AddFavoriteSticker -> Value
$ctoJSON :: AddFavoriteSticker -> Value
parseJSONList :: Value -> Parser [AddFavoriteSticker]
$cparseJSONList :: Value -> Parser [AddFavoriteSticker]
parseJSON :: Value -> Parser AddFavoriteSticker
$cparseJSON :: Value -> Parser AddFavoriteSticker
toEncodingList :: [RemoveFavoriteSticker] -> Encoding
$ctoEncodingList :: [RemoveFavoriteSticker] -> Encoding
toJSONList :: [RemoveFavoriteSticker] -> Value
$ctoJSONList :: [RemoveFavoriteSticker] -> Value
toEncoding :: RemoveFavoriteSticker -> Encoding
$ctoEncoding :: RemoveFavoriteSticker -> Encoding
toJSON :: RemoveFavoriteSticker -> Value
$ctoJSON :: RemoveFavoriteSticker -> Value
parseJSONList :: Value -> Parser [RemoveFavoriteSticker]
$cparseJSONList :: Value -> Parser [RemoveFavoriteSticker]
parseJSON :: Value -> Parser RemoveFavoriteSticker
$cparseJSON :: Value -> Parser RemoveFavoriteSticker
toEncodingList :: [GetStickerEmojis] -> Encoding
$ctoEncodingList :: [GetStickerEmojis] -> Encoding
toJSONList :: [GetStickerEmojis] -> Value
$ctoJSONList :: [GetStickerEmojis] -> Value
toEncoding :: GetStickerEmojis -> Encoding
$ctoEncoding :: GetStickerEmojis -> Encoding
toJSON :: GetStickerEmojis -> Value
$ctoJSON :: GetStickerEmojis -> Value
parseJSONList :: Value -> Parser [GetStickerEmojis]
$cparseJSONList :: Value -> Parser [GetStickerEmojis]
parseJSON :: Value -> Parser GetStickerEmojis
$cparseJSON :: Value -> Parser GetStickerEmojis
toEncodingList :: [SearchEmojis] -> Encoding
$ctoEncodingList :: [SearchEmojis] -> Encoding
toJSONList :: [SearchEmojis] -> Value
$ctoJSONList :: [SearchEmojis] -> Value
toEncoding :: SearchEmojis -> Encoding
$ctoEncoding :: SearchEmojis -> Encoding
toJSON :: SearchEmojis -> Value
$ctoJSON :: SearchEmojis -> Value
parseJSONList :: Value -> Parser [SearchEmojis]
$cparseJSONList :: Value -> Parser [SearchEmojis]
parseJSON :: Value -> Parser SearchEmojis
$cparseJSON :: Value -> Parser SearchEmojis
toEncodingList :: [GetEmojiSuggestionsUrl] -> Encoding
$ctoEncodingList :: [GetEmojiSuggestionsUrl] -> Encoding
toJSONList :: [GetEmojiSuggestionsUrl] -> Value
$ctoJSONList :: [GetEmojiSuggestionsUrl] -> Value
toEncoding :: GetEmojiSuggestionsUrl -> Encoding
$ctoEncoding :: GetEmojiSuggestionsUrl -> Encoding
toJSON :: GetEmojiSuggestionsUrl -> Value
$ctoJSON :: GetEmojiSuggestionsUrl -> Value
parseJSONList :: Value -> Parser [GetEmojiSuggestionsUrl]
$cparseJSONList :: Value -> Parser [GetEmojiSuggestionsUrl]
parseJSON :: Value -> Parser GetEmojiSuggestionsUrl
$cparseJSON :: Value -> Parser GetEmojiSuggestionsUrl
toEncodingList :: [GetSavedAnimations] -> Encoding
$ctoEncodingList :: [GetSavedAnimations] -> Encoding
toJSONList :: [GetSavedAnimations] -> Value
$ctoJSONList :: [GetSavedAnimations] -> Value
toEncoding :: GetSavedAnimations -> Encoding
$ctoEncoding :: GetSavedAnimations -> Encoding
toJSON :: GetSavedAnimations -> Value
$ctoJSON :: GetSavedAnimations -> Value
parseJSONList :: Value -> Parser [GetSavedAnimations]
$cparseJSONList :: Value -> Parser [GetSavedAnimations]
parseJSON :: Value -> Parser GetSavedAnimations
$cparseJSON :: Value -> Parser GetSavedAnimations
toEncodingList :: [AddSavedAnimation] -> Encoding
$ctoEncodingList :: [AddSavedAnimation] -> Encoding
toJSONList :: [AddSavedAnimation] -> Value
$ctoJSONList :: [AddSavedAnimation] -> Value
toEncoding :: AddSavedAnimation -> Encoding
$ctoEncoding :: AddSavedAnimation -> Encoding
toJSON :: AddSavedAnimation -> Value
$ctoJSON :: AddSavedAnimation -> Value
parseJSONList :: Value -> Parser [AddSavedAnimation]
$cparseJSONList :: Value -> Parser [AddSavedAnimation]
parseJSON :: Value -> Parser AddSavedAnimation
$cparseJSON :: Value -> Parser AddSavedAnimation
toEncodingList :: [RemoveSavedAnimation] -> Encoding
$ctoEncodingList :: [RemoveSavedAnimation] -> Encoding
toJSONList :: [RemoveSavedAnimation] -> Value
$ctoJSONList :: [RemoveSavedAnimation] -> Value
toEncoding :: RemoveSavedAnimation -> Encoding
$ctoEncoding :: RemoveSavedAnimation -> Encoding
toJSON :: RemoveSavedAnimation -> Value
$ctoJSON :: RemoveSavedAnimation -> Value
parseJSONList :: Value -> Parser [RemoveSavedAnimation]
$cparseJSONList :: Value -> Parser [RemoveSavedAnimation]
parseJSON :: Value -> Parser RemoveSavedAnimation
$cparseJSON :: Value -> Parser RemoveSavedAnimation
toEncodingList :: [GetRecentInlineBots] -> Encoding
$ctoEncodingList :: [GetRecentInlineBots] -> Encoding
toJSONList :: [GetRecentInlineBots] -> Value
$ctoJSONList :: [GetRecentInlineBots] -> Value
toEncoding :: GetRecentInlineBots -> Encoding
$ctoEncoding :: GetRecentInlineBots -> Encoding
toJSON :: GetRecentInlineBots -> Value
$ctoJSON :: GetRecentInlineBots -> Value
parseJSONList :: Value -> Parser [GetRecentInlineBots]
$cparseJSONList :: Value -> Parser [GetRecentInlineBots]
parseJSON :: Value -> Parser GetRecentInlineBots
$cparseJSON :: Value -> Parser GetRecentInlineBots
toEncodingList :: [SearchHashtags] -> Encoding
$ctoEncodingList :: [SearchHashtags] -> Encoding
toJSONList :: [SearchHashtags] -> Value
$ctoJSONList :: [SearchHashtags] -> Value
toEncoding :: SearchHashtags -> Encoding
$ctoEncoding :: SearchHashtags -> Encoding
toJSON :: SearchHashtags -> Value
$ctoJSON :: SearchHashtags -> Value
parseJSONList :: Value -> Parser [SearchHashtags]
$cparseJSONList :: Value -> Parser [SearchHashtags]
parseJSON :: Value -> Parser SearchHashtags
$cparseJSON :: Value -> Parser SearchHashtags
toEncodingList :: [RemoveRecentHashtag] -> Encoding
$ctoEncodingList :: [RemoveRecentHashtag] -> Encoding
toJSONList :: [RemoveRecentHashtag] -> Value
$ctoJSONList :: [RemoveRecentHashtag] -> Value
toEncoding :: RemoveRecentHashtag -> Encoding
$ctoEncoding :: RemoveRecentHashtag -> Encoding
toJSON :: RemoveRecentHashtag -> Value
$ctoJSON :: RemoveRecentHashtag -> Value
parseJSONList :: Value -> Parser [RemoveRecentHashtag]
$cparseJSONList :: Value -> Parser [RemoveRecentHashtag]
parseJSON :: Value -> Parser RemoveRecentHashtag
$cparseJSON :: Value -> Parser RemoveRecentHashtag
toEncodingList :: [GetWebPagePreview] -> Encoding
$ctoEncodingList :: [GetWebPagePreview] -> Encoding
toJSONList :: [GetWebPagePreview] -> Value
$ctoJSONList :: [GetWebPagePreview] -> Value
toEncoding :: GetWebPagePreview -> Encoding
$ctoEncoding :: GetWebPagePreview -> Encoding
toJSON :: GetWebPagePreview -> Value
$ctoJSON :: GetWebPagePreview -> Value
parseJSONList :: Value -> Parser [GetWebPagePreview]
$cparseJSONList :: Value -> Parser [GetWebPagePreview]
parseJSON :: Value -> Parser GetWebPagePreview
$cparseJSON :: Value -> Parser GetWebPagePreview
toEncodingList :: [GetWebPageInstantView] -> Encoding
$ctoEncodingList :: [GetWebPageInstantView] -> Encoding
toJSONList :: [GetWebPageInstantView] -> Value
$ctoJSONList :: [GetWebPageInstantView] -> Value
toEncoding :: GetWebPageInstantView -> Encoding
$ctoEncoding :: GetWebPageInstantView -> Encoding
toJSON :: GetWebPageInstantView -> Value
$ctoJSON :: GetWebPageInstantView -> Value
parseJSONList :: Value -> Parser [GetWebPageInstantView]
$cparseJSONList :: Value -> Parser [GetWebPageInstantView]
parseJSON :: Value -> Parser GetWebPageInstantView
$cparseJSON :: Value -> Parser GetWebPageInstantView
toEncodingList :: [SetProfilePhoto] -> Encoding
$ctoEncodingList :: [SetProfilePhoto] -> Encoding
toJSONList :: [SetProfilePhoto] -> Value
$ctoJSONList :: [SetProfilePhoto] -> Value
toEncoding :: SetProfilePhoto -> Encoding
$ctoEncoding :: SetProfilePhoto -> Encoding
toJSON :: SetProfilePhoto -> Value
$ctoJSON :: SetProfilePhoto -> Value
parseJSONList :: Value -> Parser [SetProfilePhoto]
$cparseJSONList :: Value -> Parser [SetProfilePhoto]
parseJSON :: Value -> Parser SetProfilePhoto
$cparseJSON :: Value -> Parser SetProfilePhoto
toEncodingList :: [DeleteProfilePhoto] -> Encoding
$ctoEncodingList :: [DeleteProfilePhoto] -> Encoding
toJSONList :: [DeleteProfilePhoto] -> Value
$ctoJSONList :: [DeleteProfilePhoto] -> Value
toEncoding :: DeleteProfilePhoto -> Encoding
$ctoEncoding :: DeleteProfilePhoto -> Encoding
toJSON :: DeleteProfilePhoto -> Value
$ctoJSON :: DeleteProfilePhoto -> Value
parseJSONList :: Value -> Parser [DeleteProfilePhoto]
$cparseJSONList :: Value -> Parser [DeleteProfilePhoto]
parseJSON :: Value -> Parser DeleteProfilePhoto
$cparseJSON :: Value -> Parser DeleteProfilePhoto
toEncodingList :: [SetName] -> Encoding
$ctoEncodingList :: [SetName] -> Encoding
toJSONList :: [SetName] -> Value
$ctoJSONList :: [SetName] -> Value
toEncoding :: SetName -> Encoding
$ctoEncoding :: SetName -> Encoding
toJSON :: SetName -> Value
$ctoJSON :: SetName -> Value
parseJSONList :: Value -> Parser [SetName]
$cparseJSONList :: Value -> Parser [SetName]
parseJSON :: Value -> Parser SetName
$cparseJSON :: Value -> Parser SetName
toEncodingList :: [SetBio] -> Encoding
$ctoEncodingList :: [SetBio] -> Encoding
toJSONList :: [SetBio] -> Value
$ctoJSONList :: [SetBio] -> Value
toEncoding :: SetBio -> Encoding
$ctoEncoding :: SetBio -> Encoding
toJSON :: SetBio -> Value
$ctoJSON :: SetBio -> Value
parseJSONList :: Value -> Parser [SetBio]
$cparseJSONList :: Value -> Parser [SetBio]
parseJSON :: Value -> Parser SetBio
$cparseJSON :: Value -> Parser SetBio
toEncodingList :: [SetUsername] -> Encoding
$ctoEncodingList :: [SetUsername] -> Encoding
toJSONList :: [SetUsername] -> Value
$ctoJSONList :: [SetUsername] -> Value
toEncoding :: SetUsername -> Encoding
$ctoEncoding :: SetUsername -> Encoding
toJSON :: SetUsername -> Value
$ctoJSON :: SetUsername -> Value
parseJSONList :: Value -> Parser [SetUsername]
$cparseJSONList :: Value -> Parser [SetUsername]
parseJSON :: Value -> Parser SetUsername
$cparseJSON :: Value -> Parser SetUsername
toEncodingList :: [SetLocation] -> Encoding
$ctoEncodingList :: [SetLocation] -> Encoding
toJSONList :: [SetLocation] -> Value
$ctoJSONList :: [SetLocation] -> Value
toEncoding :: SetLocation -> Encoding
$ctoEncoding :: SetLocation -> Encoding
toJSON :: SetLocation -> Value
$ctoJSON :: SetLocation -> Value
parseJSONList :: Value -> Parser [SetLocation]
$cparseJSONList :: Value -> Parser [SetLocation]
parseJSON :: Value -> Parser SetLocation
$cparseJSON :: Value -> Parser SetLocation
toEncodingList :: [ChangePhoneNumber] -> Encoding
$ctoEncodingList :: [ChangePhoneNumber] -> Encoding
toJSONList :: [ChangePhoneNumber] -> Value
$ctoJSONList :: [ChangePhoneNumber] -> Value
toEncoding :: ChangePhoneNumber -> Encoding
$ctoEncoding :: ChangePhoneNumber -> Encoding
toJSON :: ChangePhoneNumber -> Value
$ctoJSON :: ChangePhoneNumber -> Value
parseJSONList :: Value -> Parser [ChangePhoneNumber]
$cparseJSONList :: Value -> Parser [ChangePhoneNumber]
parseJSON :: Value -> Parser ChangePhoneNumber
$cparseJSON :: Value -> Parser ChangePhoneNumber
toEncodingList :: [ResendChangePhoneNumberCode] -> Encoding
$ctoEncodingList :: [ResendChangePhoneNumberCode] -> Encoding
toJSONList :: [ResendChangePhoneNumberCode] -> Value
$ctoJSONList :: [ResendChangePhoneNumberCode] -> Value
toEncoding :: ResendChangePhoneNumberCode -> Encoding
$ctoEncoding :: ResendChangePhoneNumberCode -> Encoding
toJSON :: ResendChangePhoneNumberCode -> Value
$ctoJSON :: ResendChangePhoneNumberCode -> Value
parseJSONList :: Value -> Parser [ResendChangePhoneNumberCode]
$cparseJSONList :: Value -> Parser [ResendChangePhoneNumberCode]
parseJSON :: Value -> Parser ResendChangePhoneNumberCode
$cparseJSON :: Value -> Parser ResendChangePhoneNumberCode
toEncodingList :: [CheckChangePhoneNumberCode] -> Encoding
$ctoEncodingList :: [CheckChangePhoneNumberCode] -> Encoding
toJSONList :: [CheckChangePhoneNumberCode] -> Value
$ctoJSONList :: [CheckChangePhoneNumberCode] -> Value
toEncoding :: CheckChangePhoneNumberCode -> Encoding
$ctoEncoding :: CheckChangePhoneNumberCode -> Encoding
toJSON :: CheckChangePhoneNumberCode -> Value
$ctoJSON :: CheckChangePhoneNumberCode -> Value
parseJSONList :: Value -> Parser [CheckChangePhoneNumberCode]
$cparseJSONList :: Value -> Parser [CheckChangePhoneNumberCode]
parseJSON :: Value -> Parser CheckChangePhoneNumberCode
$cparseJSON :: Value -> Parser CheckChangePhoneNumberCode
toEncodingList :: [SetCommands] -> Encoding
$ctoEncodingList :: [SetCommands] -> Encoding
toJSONList :: [SetCommands] -> Value
$ctoJSONList :: [SetCommands] -> Value
toEncoding :: SetCommands -> Encoding
$ctoEncoding :: SetCommands -> Encoding
toJSON :: SetCommands -> Value
$ctoJSON :: SetCommands -> Value
parseJSONList :: Value -> Parser [SetCommands]
$cparseJSONList :: Value -> Parser [SetCommands]
parseJSON :: Value -> Parser SetCommands
$cparseJSON :: Value -> Parser SetCommands
toEncodingList :: [GetActiveSessions] -> Encoding
$ctoEncodingList :: [GetActiveSessions] -> Encoding
toJSONList :: [GetActiveSessions] -> Value
$ctoJSONList :: [GetActiveSessions] -> Value
toEncoding :: GetActiveSessions -> Encoding
$ctoEncoding :: GetActiveSessions -> Encoding
toJSON :: GetActiveSessions -> Value
$ctoJSON :: GetActiveSessions -> Value
parseJSONList :: Value -> Parser [GetActiveSessions]
$cparseJSONList :: Value -> Parser [GetActiveSessions]
parseJSON :: Value -> Parser GetActiveSessions
$cparseJSON :: Value -> Parser GetActiveSessions
toEncodingList :: [TerminateSession] -> Encoding
$ctoEncodingList :: [TerminateSession] -> Encoding
toJSONList :: [TerminateSession] -> Value
$ctoJSONList :: [TerminateSession] -> Value
toEncoding :: TerminateSession -> Encoding
$ctoEncoding :: TerminateSession -> Encoding
toJSON :: TerminateSession -> Value
$ctoJSON :: TerminateSession -> Value
parseJSONList :: Value -> Parser [TerminateSession]
$cparseJSONList :: Value -> Parser [TerminateSession]
parseJSON :: Value -> Parser TerminateSession
$cparseJSON :: Value -> Parser TerminateSession
toEncodingList :: [TerminateAllOtherSessions] -> Encoding
$ctoEncodingList :: [TerminateAllOtherSessions] -> Encoding
toJSONList :: [TerminateAllOtherSessions] -> Value
$ctoJSONList :: [TerminateAllOtherSessions] -> Value
toEncoding :: TerminateAllOtherSessions -> Encoding
$ctoEncoding :: TerminateAllOtherSessions -> Encoding
toJSON :: TerminateAllOtherSessions -> Value
$ctoJSON :: TerminateAllOtherSessions -> Value
parseJSONList :: Value -> Parser [TerminateAllOtherSessions]
$cparseJSONList :: Value -> Parser [TerminateAllOtherSessions]
parseJSON :: Value -> Parser TerminateAllOtherSessions
$cparseJSON :: Value -> Parser TerminateAllOtherSessions
toEncodingList :: [GetConnectedWebsites] -> Encoding
$ctoEncodingList :: [GetConnectedWebsites] -> Encoding
toJSONList :: [GetConnectedWebsites] -> Value
$ctoJSONList :: [GetConnectedWebsites] -> Value
toEncoding :: GetConnectedWebsites -> Encoding
$ctoEncoding :: GetConnectedWebsites -> Encoding
toJSON :: GetConnectedWebsites -> Value
$ctoJSON :: GetConnectedWebsites -> Value
parseJSONList :: Value -> Parser [GetConnectedWebsites]
$cparseJSONList :: Value -> Parser [GetConnectedWebsites]
parseJSON :: Value -> Parser GetConnectedWebsites
$cparseJSON :: Value -> Parser GetConnectedWebsites
toEncodingList :: [DisconnectWebsite] -> Encoding
$ctoEncodingList :: [DisconnectWebsite] -> Encoding
toJSONList :: [DisconnectWebsite] -> Value
$ctoJSONList :: [DisconnectWebsite] -> Value
toEncoding :: DisconnectWebsite -> Encoding
$ctoEncoding :: DisconnectWebsite -> Encoding
toJSON :: DisconnectWebsite -> Value
$ctoJSON :: DisconnectWebsite -> Value
parseJSONList :: Value -> Parser [DisconnectWebsite]
$cparseJSONList :: Value -> Parser [DisconnectWebsite]
parseJSON :: Value -> Parser DisconnectWebsite
$cparseJSON :: Value -> Parser DisconnectWebsite
toEncodingList :: [DisconnectAllWebsites] -> Encoding
$ctoEncodingList :: [DisconnectAllWebsites] -> Encoding
toJSONList :: [DisconnectAllWebsites] -> Value
$ctoJSONList :: [DisconnectAllWebsites] -> Value
toEncoding :: DisconnectAllWebsites -> Encoding
$ctoEncoding :: DisconnectAllWebsites -> Encoding
toJSON :: DisconnectAllWebsites -> Value
$ctoJSON :: DisconnectAllWebsites -> Value
parseJSONList :: Value -> Parser [DisconnectAllWebsites]
$cparseJSONList :: Value -> Parser [DisconnectAllWebsites]
parseJSON :: Value -> Parser DisconnectAllWebsites
$cparseJSON :: Value -> Parser DisconnectAllWebsites
toEncodingList :: [SetSupergroupUsername] -> Encoding
$ctoEncodingList :: [SetSupergroupUsername] -> Encoding
toJSONList :: [SetSupergroupUsername] -> Value
$ctoJSONList :: [SetSupergroupUsername] -> Value
toEncoding :: SetSupergroupUsername -> Encoding
$ctoEncoding :: SetSupergroupUsername -> Encoding
toJSON :: SetSupergroupUsername -> Value
$ctoJSON :: SetSupergroupUsername -> Value
parseJSONList :: Value -> Parser [SetSupergroupUsername]
$cparseJSONList :: Value -> Parser [SetSupergroupUsername]
parseJSON :: Value -> Parser SetSupergroupUsername
$cparseJSON :: Value -> Parser SetSupergroupUsername
toEncodingList :: [SetSupergroupStickerSet] -> Encoding
$ctoEncodingList :: [SetSupergroupStickerSet] -> Encoding
toJSONList :: [SetSupergroupStickerSet] -> Value
$ctoJSONList :: [SetSupergroupStickerSet] -> Value
toEncoding :: SetSupergroupStickerSet -> Encoding
$ctoEncoding :: SetSupergroupStickerSet -> Encoding
toJSON :: SetSupergroupStickerSet -> Value
$ctoJSON :: SetSupergroupStickerSet -> Value
parseJSONList :: Value -> Parser [SetSupergroupStickerSet]
$cparseJSONList :: Value -> Parser [SetSupergroupStickerSet]
parseJSON :: Value -> Parser SetSupergroupStickerSet
$cparseJSON :: Value -> Parser SetSupergroupStickerSet
toEncodingList :: [ToggleSupergroupSignMessages] -> Encoding
$ctoEncodingList :: [ToggleSupergroupSignMessages] -> Encoding
toJSONList :: [ToggleSupergroupSignMessages] -> Value
$ctoJSONList :: [ToggleSupergroupSignMessages] -> Value
toEncoding :: ToggleSupergroupSignMessages -> Encoding
$ctoEncoding :: ToggleSupergroupSignMessages -> Encoding
toJSON :: ToggleSupergroupSignMessages -> Value
$ctoJSON :: ToggleSupergroupSignMessages -> Value
parseJSONList :: Value -> Parser [ToggleSupergroupSignMessages]
$cparseJSONList :: Value -> Parser [ToggleSupergroupSignMessages]
parseJSON :: Value -> Parser ToggleSupergroupSignMessages
$cparseJSON :: Value -> Parser ToggleSupergroupSignMessages
toEncodingList :: [ToggleSupergroupIsAllHistoryAvailable] -> Encoding
$ctoEncodingList :: [ToggleSupergroupIsAllHistoryAvailable] -> Encoding
toJSONList :: [ToggleSupergroupIsAllHistoryAvailable] -> Value
$ctoJSONList :: [ToggleSupergroupIsAllHistoryAvailable] -> Value
toEncoding :: ToggleSupergroupIsAllHistoryAvailable -> Encoding
$ctoEncoding :: ToggleSupergroupIsAllHistoryAvailable -> Encoding
toJSON :: ToggleSupergroupIsAllHistoryAvailable -> Value
$ctoJSON :: ToggleSupergroupIsAllHistoryAvailable -> Value
parseJSONList :: Value -> Parser [ToggleSupergroupIsAllHistoryAvailable]
$cparseJSONList :: Value -> Parser [ToggleSupergroupIsAllHistoryAvailable]
parseJSON :: Value -> Parser ToggleSupergroupIsAllHistoryAvailable
$cparseJSON :: Value -> Parser ToggleSupergroupIsAllHistoryAvailable
toEncodingList :: [ReportSupergroupSpam] -> Encoding
$ctoEncodingList :: [ReportSupergroupSpam] -> Encoding
toJSONList :: [ReportSupergroupSpam] -> Value
$ctoJSONList :: [ReportSupergroupSpam] -> Value
toEncoding :: ReportSupergroupSpam -> Encoding
$ctoEncoding :: ReportSupergroupSpam -> Encoding
toJSON :: ReportSupergroupSpam -> Value
$ctoJSON :: ReportSupergroupSpam -> Value
parseJSONList :: Value -> Parser [ReportSupergroupSpam]
$cparseJSONList :: Value -> Parser [ReportSupergroupSpam]
parseJSON :: Value -> Parser ReportSupergroupSpam
$cparseJSON :: Value -> Parser ReportSupergroupSpam
toEncodingList :: [GetSupergroupMembers] -> Encoding
$ctoEncodingList :: [GetSupergroupMembers] -> Encoding
toJSONList :: [GetSupergroupMembers] -> Value
$ctoJSONList :: [GetSupergroupMembers] -> Value
toEncoding :: GetSupergroupMembers -> Encoding
$ctoEncoding :: GetSupergroupMembers -> Encoding
toJSON :: GetSupergroupMembers -> Value
$ctoJSON :: GetSupergroupMembers -> Value
parseJSONList :: Value -> Parser [GetSupergroupMembers]
$cparseJSONList :: Value -> Parser [GetSupergroupMembers]
parseJSON :: Value -> Parser GetSupergroupMembers
$cparseJSON :: Value -> Parser GetSupergroupMembers
toEncodingList :: [DeleteSupergroup] -> Encoding
$ctoEncodingList :: [DeleteSupergroup] -> Encoding
toJSONList :: [DeleteSupergroup] -> Value
$ctoJSONList :: [DeleteSupergroup] -> Value
toEncoding :: DeleteSupergroup -> Encoding
$ctoEncoding :: DeleteSupergroup -> Encoding
toJSON :: DeleteSupergroup -> Value
$ctoJSON :: DeleteSupergroup -> Value
parseJSONList :: Value -> Parser [DeleteSupergroup]
$cparseJSONList :: Value -> Parser [DeleteSupergroup]
parseJSON :: Value -> Parser DeleteSupergroup
$cparseJSON :: Value -> Parser DeleteSupergroup
toEncodingList :: [CloseSecretChat] -> Encoding
$ctoEncodingList :: [CloseSecretChat] -> Encoding
toJSONList :: [CloseSecretChat] -> Value
$ctoJSONList :: [CloseSecretChat] -> Value
toEncoding :: CloseSecretChat -> Encoding
$ctoEncoding :: CloseSecretChat -> Encoding
toJSON :: CloseSecretChat -> Value
$ctoJSON :: CloseSecretChat -> Value
parseJSONList :: Value -> Parser [CloseSecretChat]
$cparseJSONList :: Value -> Parser [CloseSecretChat]
parseJSON :: Value -> Parser CloseSecretChat
$cparseJSON :: Value -> Parser CloseSecretChat
toEncodingList :: [GetChatEventLog] -> Encoding
$ctoEncodingList :: [GetChatEventLog] -> Encoding
toJSONList :: [GetChatEventLog] -> Value
$ctoJSONList :: [GetChatEventLog] -> Value
toEncoding :: GetChatEventLog -> Encoding
$ctoEncoding :: GetChatEventLog -> Encoding
toJSON :: GetChatEventLog -> Value
$ctoJSON :: GetChatEventLog -> Value
parseJSONList :: Value -> Parser [GetChatEventLog]
$cparseJSONList :: Value -> Parser [GetChatEventLog]
parseJSON :: Value -> Parser GetChatEventLog
$cparseJSON :: Value -> Parser GetChatEventLog
toEncodingList :: [GetPaymentForm] -> Encoding
$ctoEncodingList :: [GetPaymentForm] -> Encoding
toJSONList :: [GetPaymentForm] -> Value
$ctoJSONList :: [GetPaymentForm] -> Value
toEncoding :: GetPaymentForm -> Encoding
$ctoEncoding :: GetPaymentForm -> Encoding
toJSON :: GetPaymentForm -> Value
$ctoJSON :: GetPaymentForm -> Value
parseJSONList :: Value -> Parser [GetPaymentForm]
$cparseJSONList :: Value -> Parser [GetPaymentForm]
parseJSON :: Value -> Parser GetPaymentForm
$cparseJSON :: Value -> Parser GetPaymentForm
toEncodingList :: [ValidateOrderInfo] -> Encoding
$ctoEncodingList :: [ValidateOrderInfo] -> Encoding
toJSONList :: [ValidateOrderInfo] -> Value
$ctoJSONList :: [ValidateOrderInfo] -> Value
toEncoding :: ValidateOrderInfo -> Encoding
$ctoEncoding :: ValidateOrderInfo -> Encoding
toJSON :: ValidateOrderInfo -> Value
$ctoJSON :: ValidateOrderInfo -> Value
parseJSONList :: Value -> Parser [ValidateOrderInfo]
$cparseJSONList :: Value -> Parser [ValidateOrderInfo]
parseJSON :: Value -> Parser ValidateOrderInfo
$cparseJSON :: Value -> Parser ValidateOrderInfo
toEncodingList :: [SendPaymentForm] -> Encoding
$ctoEncodingList :: [SendPaymentForm] -> Encoding
toJSONList :: [SendPaymentForm] -> Value
$ctoJSONList :: [SendPaymentForm] -> Value
toEncoding :: SendPaymentForm -> Encoding
$ctoEncoding :: SendPaymentForm -> Encoding
toJSON :: SendPaymentForm -> Value
$ctoJSON :: SendPaymentForm -> Value
parseJSONList :: Value -> Parser [SendPaymentForm]
$cparseJSONList :: Value -> Parser [SendPaymentForm]
parseJSON :: Value -> Parser SendPaymentForm
$cparseJSON :: Value -> Parser SendPaymentForm
toEncodingList :: [GetPaymentReceipt] -> Encoding
$ctoEncodingList :: [GetPaymentReceipt] -> Encoding
toJSONList :: [GetPaymentReceipt] -> Value
$ctoJSONList :: [GetPaymentReceipt] -> Value
toEncoding :: GetPaymentReceipt -> Encoding
$ctoEncoding :: GetPaymentReceipt -> Encoding
toJSON :: GetPaymentReceipt -> Value
$ctoJSON :: GetPaymentReceipt -> Value
parseJSONList :: Value -> Parser [GetPaymentReceipt]
$cparseJSONList :: Value -> Parser [GetPaymentReceipt]
parseJSON :: Value -> Parser GetPaymentReceipt
$cparseJSON :: Value -> Parser GetPaymentReceipt
toEncodingList :: [GetSavedOrderInfo] -> Encoding
$ctoEncodingList :: [GetSavedOrderInfo] -> Encoding
toJSONList :: [GetSavedOrderInfo] -> Value
$ctoJSONList :: [GetSavedOrderInfo] -> Value
toEncoding :: GetSavedOrderInfo -> Encoding
$ctoEncoding :: GetSavedOrderInfo -> Encoding
toJSON :: GetSavedOrderInfo -> Value
$ctoJSON :: GetSavedOrderInfo -> Value
parseJSONList :: Value -> Parser [GetSavedOrderInfo]
$cparseJSONList :: Value -> Parser [GetSavedOrderInfo]
parseJSON :: Value -> Parser GetSavedOrderInfo
$cparseJSON :: Value -> Parser GetSavedOrderInfo
toEncodingList :: [DeleteSavedOrderInfo] -> Encoding
$ctoEncodingList :: [DeleteSavedOrderInfo] -> Encoding
toJSONList :: [DeleteSavedOrderInfo] -> Value
$ctoJSONList :: [DeleteSavedOrderInfo] -> Value
toEncoding :: DeleteSavedOrderInfo -> Encoding
$ctoEncoding :: DeleteSavedOrderInfo -> Encoding
toJSON :: DeleteSavedOrderInfo -> Value
$ctoJSON :: DeleteSavedOrderInfo -> Value
parseJSONList :: Value -> Parser [DeleteSavedOrderInfo]
$cparseJSONList :: Value -> Parser [DeleteSavedOrderInfo]
parseJSON :: Value -> Parser DeleteSavedOrderInfo
$cparseJSON :: Value -> Parser DeleteSavedOrderInfo
toEncodingList :: [DeleteSavedCredentials] -> Encoding
$ctoEncodingList :: [DeleteSavedCredentials] -> Encoding
toJSONList :: [DeleteSavedCredentials] -> Value
$ctoJSONList :: [DeleteSavedCredentials] -> Value
toEncoding :: DeleteSavedCredentials -> Encoding
$ctoEncoding :: DeleteSavedCredentials -> Encoding
toJSON :: DeleteSavedCredentials -> Value
$ctoJSON :: DeleteSavedCredentials -> Value
parseJSONList :: Value -> Parser [DeleteSavedCredentials]
$cparseJSONList :: Value -> Parser [DeleteSavedCredentials]
parseJSON :: Value -> Parser DeleteSavedCredentials
$cparseJSON :: Value -> Parser DeleteSavedCredentials
toEncodingList :: [GetSupportUser] -> Encoding
$ctoEncodingList :: [GetSupportUser] -> Encoding
toJSONList :: [GetSupportUser] -> Value
$ctoJSONList :: [GetSupportUser] -> Value
toEncoding :: GetSupportUser -> Encoding
$ctoEncoding :: GetSupportUser -> Encoding
toJSON :: GetSupportUser -> Value
$ctoJSON :: GetSupportUser -> Value
parseJSONList :: Value -> Parser [GetSupportUser]
$cparseJSONList :: Value -> Parser [GetSupportUser]
parseJSON :: Value -> Parser GetSupportUser
$cparseJSON :: Value -> Parser GetSupportUser
toEncodingList :: [GetBackgrounds] -> Encoding
$ctoEncodingList :: [GetBackgrounds] -> Encoding
toJSONList :: [GetBackgrounds] -> Value
$ctoJSONList :: [GetBackgrounds] -> Value
toEncoding :: GetBackgrounds -> Encoding
$ctoEncoding :: GetBackgrounds -> Encoding
toJSON :: GetBackgrounds -> Value
$ctoJSON :: GetBackgrounds -> Value
parseJSONList :: Value -> Parser [GetBackgrounds]
$cparseJSONList :: Value -> Parser [GetBackgrounds]
parseJSON :: Value -> Parser GetBackgrounds
$cparseJSON :: Value -> Parser GetBackgrounds
toEncodingList :: [GetBackgroundUrl] -> Encoding
$ctoEncodingList :: [GetBackgroundUrl] -> Encoding
toJSONList :: [GetBackgroundUrl] -> Value
$ctoJSONList :: [GetBackgroundUrl] -> Value
toEncoding :: GetBackgroundUrl -> Encoding
$ctoEncoding :: GetBackgroundUrl -> Encoding
toJSON :: GetBackgroundUrl -> Value
$ctoJSON :: GetBackgroundUrl -> Value
parseJSONList :: Value -> Parser [GetBackgroundUrl]
$cparseJSONList :: Value -> Parser [GetBackgroundUrl]
parseJSON :: Value -> Parser GetBackgroundUrl
$cparseJSON :: Value -> Parser GetBackgroundUrl
toEncodingList :: [SearchBackground] -> Encoding
$ctoEncodingList :: [SearchBackground] -> Encoding
toJSONList :: [SearchBackground] -> Value
$ctoJSONList :: [SearchBackground] -> Value
toEncoding :: SearchBackground -> Encoding
$ctoEncoding :: SearchBackground -> Encoding
toJSON :: SearchBackground -> Value
$ctoJSON :: SearchBackground -> Value
parseJSONList :: Value -> Parser [SearchBackground]
$cparseJSONList :: Value -> Parser [SearchBackground]
parseJSON :: Value -> Parser SearchBackground
$cparseJSON :: Value -> Parser SearchBackground
toEncodingList :: [SetBackground] -> Encoding
$ctoEncodingList :: [SetBackground] -> Encoding
toJSONList :: [SetBackground] -> Value
$ctoJSONList :: [SetBackground] -> Value
toEncoding :: SetBackground -> Encoding
$ctoEncoding :: SetBackground -> Encoding
toJSON :: SetBackground -> Value
$ctoJSON :: SetBackground -> Value
parseJSONList :: Value -> Parser [SetBackground]
$cparseJSONList :: Value -> Parser [SetBackground]
parseJSON :: Value -> Parser SetBackground
$cparseJSON :: Value -> Parser SetBackground
toEncodingList :: [RemoveBackground] -> Encoding
$ctoEncodingList :: [RemoveBackground] -> Encoding
toJSONList :: [RemoveBackground] -> Value
$ctoJSONList :: [RemoveBackground] -> Value
toEncoding :: RemoveBackground -> Encoding
$ctoEncoding :: RemoveBackground -> Encoding
toJSON :: RemoveBackground -> Value
$ctoJSON :: RemoveBackground -> Value
parseJSONList :: Value -> Parser [RemoveBackground]
$cparseJSONList :: Value -> Parser [RemoveBackground]
parseJSON :: Value -> Parser RemoveBackground
$cparseJSON :: Value -> Parser RemoveBackground
toEncodingList :: [ResetBackgrounds] -> Encoding
$ctoEncodingList :: [ResetBackgrounds] -> Encoding
toJSONList :: [ResetBackgrounds] -> Value
$ctoJSONList :: [ResetBackgrounds] -> Value
toEncoding :: ResetBackgrounds -> Encoding
$ctoEncoding :: ResetBackgrounds -> Encoding
toJSON :: ResetBackgrounds -> Value
$ctoJSON :: ResetBackgrounds -> Value
parseJSONList :: Value -> Parser [ResetBackgrounds]
$cparseJSONList :: Value -> Parser [ResetBackgrounds]
parseJSON :: Value -> Parser ResetBackgrounds
$cparseJSON :: Value -> Parser ResetBackgrounds
toEncodingList :: [GetLocalizationTargetInfo] -> Encoding
$ctoEncodingList :: [GetLocalizationTargetInfo] -> Encoding
toJSONList :: [GetLocalizationTargetInfo] -> Value
$ctoJSONList :: [GetLocalizationTargetInfo] -> Value
toEncoding :: GetLocalizationTargetInfo -> Encoding
$ctoEncoding :: GetLocalizationTargetInfo -> Encoding
toJSON :: GetLocalizationTargetInfo -> Value
$ctoJSON :: GetLocalizationTargetInfo -> Value
parseJSONList :: Value -> Parser [GetLocalizationTargetInfo]
$cparseJSONList :: Value -> Parser [GetLocalizationTargetInfo]
parseJSON :: Value -> Parser GetLocalizationTargetInfo
$cparseJSON :: Value -> Parser GetLocalizationTargetInfo
toEncodingList :: [GetLanguagePackInfo] -> Encoding
$ctoEncodingList :: [GetLanguagePackInfo] -> Encoding
toJSONList :: [GetLanguagePackInfo] -> Value
$ctoJSONList :: [GetLanguagePackInfo] -> Value
toEncoding :: GetLanguagePackInfo -> Encoding
$ctoEncoding :: GetLanguagePackInfo -> Encoding
toJSON :: GetLanguagePackInfo -> Value
$ctoJSON :: GetLanguagePackInfo -> Value
parseJSONList :: Value -> Parser [GetLanguagePackInfo]
$cparseJSONList :: Value -> Parser [GetLanguagePackInfo]
parseJSON :: Value -> Parser GetLanguagePackInfo
$cparseJSON :: Value -> Parser GetLanguagePackInfo
toEncodingList :: [GetLanguagePackStrings] -> Encoding
$ctoEncodingList :: [GetLanguagePackStrings] -> Encoding
toJSONList :: [GetLanguagePackStrings] -> Value
$ctoJSONList :: [GetLanguagePackStrings] -> Value
toEncoding :: GetLanguagePackStrings -> Encoding
$ctoEncoding :: GetLanguagePackStrings -> Encoding
toJSON :: GetLanguagePackStrings -> Value
$ctoJSON :: GetLanguagePackStrings -> Value
parseJSONList :: Value -> Parser [GetLanguagePackStrings]
$cparseJSONList :: Value -> Parser [GetLanguagePackStrings]
parseJSON :: Value -> Parser GetLanguagePackStrings
$cparseJSON :: Value -> Parser GetLanguagePackStrings
toEncodingList :: [SynchronizeLanguagePack] -> Encoding
$ctoEncodingList :: [SynchronizeLanguagePack] -> Encoding
toJSONList :: [SynchronizeLanguagePack] -> Value
$ctoJSONList :: [SynchronizeLanguagePack] -> Value
toEncoding :: SynchronizeLanguagePack -> Encoding
$ctoEncoding :: SynchronizeLanguagePack -> Encoding
toJSON :: SynchronizeLanguagePack -> Value
$ctoJSON :: SynchronizeLanguagePack -> Value
parseJSONList :: Value -> Parser [SynchronizeLanguagePack]
$cparseJSONList :: Value -> Parser [SynchronizeLanguagePack]
parseJSON :: Value -> Parser SynchronizeLanguagePack
$cparseJSON :: Value -> Parser SynchronizeLanguagePack
toEncodingList :: [AddCustomServerLanguagePack] -> Encoding
$ctoEncodingList :: [AddCustomServerLanguagePack] -> Encoding
toJSONList :: [AddCustomServerLanguagePack] -> Value
$ctoJSONList :: [AddCustomServerLanguagePack] -> Value
toEncoding :: AddCustomServerLanguagePack -> Encoding
$ctoEncoding :: AddCustomServerLanguagePack -> Encoding
toJSON :: AddCustomServerLanguagePack -> Value
$ctoJSON :: AddCustomServerLanguagePack -> Value
parseJSONList :: Value -> Parser [AddCustomServerLanguagePack]
$cparseJSONList :: Value -> Parser [AddCustomServerLanguagePack]
parseJSON :: Value -> Parser AddCustomServerLanguagePack
$cparseJSON :: Value -> Parser AddCustomServerLanguagePack
toEncodingList :: [SetCustomLanguagePack] -> Encoding
$ctoEncodingList :: [SetCustomLanguagePack] -> Encoding
toJSONList :: [SetCustomLanguagePack] -> Value
$ctoJSONList :: [SetCustomLanguagePack] -> Value
toEncoding :: SetCustomLanguagePack -> Encoding
$ctoEncoding :: SetCustomLanguagePack -> Encoding
toJSON :: SetCustomLanguagePack -> Value
$ctoJSON :: SetCustomLanguagePack -> Value
parseJSONList :: Value -> Parser [SetCustomLanguagePack]
$cparseJSONList :: Value -> Parser [SetCustomLanguagePack]
parseJSON :: Value -> Parser SetCustomLanguagePack
$cparseJSON :: Value -> Parser SetCustomLanguagePack
toEncodingList :: [EditCustomLanguagePackInfo] -> Encoding
$ctoEncodingList :: [EditCustomLanguagePackInfo] -> Encoding
toJSONList :: [EditCustomLanguagePackInfo] -> Value
$ctoJSONList :: [EditCustomLanguagePackInfo] -> Value
toEncoding :: EditCustomLanguagePackInfo -> Encoding
$ctoEncoding :: EditCustomLanguagePackInfo -> Encoding
toJSON :: EditCustomLanguagePackInfo -> Value
$ctoJSON :: EditCustomLanguagePackInfo -> Value
parseJSONList :: Value -> Parser [EditCustomLanguagePackInfo]
$cparseJSONList :: Value -> Parser [EditCustomLanguagePackInfo]
parseJSON :: Value -> Parser EditCustomLanguagePackInfo
$cparseJSON :: Value -> Parser EditCustomLanguagePackInfo
toEncodingList :: [SetCustomLanguagePackString] -> Encoding
$ctoEncodingList :: [SetCustomLanguagePackString] -> Encoding
toJSONList :: [SetCustomLanguagePackString] -> Value
$ctoJSONList :: [SetCustomLanguagePackString] -> Value
toEncoding :: SetCustomLanguagePackString -> Encoding
$ctoEncoding :: SetCustomLanguagePackString -> Encoding
toJSON :: SetCustomLanguagePackString -> Value
$ctoJSON :: SetCustomLanguagePackString -> Value
parseJSONList :: Value -> Parser [SetCustomLanguagePackString]
$cparseJSONList :: Value -> Parser [SetCustomLanguagePackString]
parseJSON :: Value -> Parser SetCustomLanguagePackString
$cparseJSON :: Value -> Parser SetCustomLanguagePackString
toEncodingList :: [DeleteLanguagePack] -> Encoding
$ctoEncodingList :: [DeleteLanguagePack] -> Encoding
toJSONList :: [DeleteLanguagePack] -> Value
$ctoJSONList :: [DeleteLanguagePack] -> Value
toEncoding :: DeleteLanguagePack -> Encoding
$ctoEncoding :: DeleteLanguagePack -> Encoding
toJSON :: DeleteLanguagePack -> Value
$ctoJSON :: DeleteLanguagePack -> Value
parseJSONList :: Value -> Parser [DeleteLanguagePack]
$cparseJSONList :: Value -> Parser [DeleteLanguagePack]
parseJSON :: Value -> Parser DeleteLanguagePack
$cparseJSON :: Value -> Parser DeleteLanguagePack
toEncodingList :: [RegisterDevice] -> Encoding
$ctoEncodingList :: [RegisterDevice] -> Encoding
toJSONList :: [RegisterDevice] -> Value
$ctoJSONList :: [RegisterDevice] -> Value
toEncoding :: RegisterDevice -> Encoding
$ctoEncoding :: RegisterDevice -> Encoding
toJSON :: RegisterDevice -> Value
$ctoJSON :: RegisterDevice -> Value
parseJSONList :: Value -> Parser [RegisterDevice]
$cparseJSONList :: Value -> Parser [RegisterDevice]
parseJSON :: Value -> Parser RegisterDevice
$cparseJSON :: Value -> Parser RegisterDevice
toEncodingList :: [ProcessPushNotification] -> Encoding
$ctoEncodingList :: [ProcessPushNotification] -> Encoding
toJSONList :: [ProcessPushNotification] -> Value
$ctoJSONList :: [ProcessPushNotification] -> Value
toEncoding :: ProcessPushNotification -> Encoding
$ctoEncoding :: ProcessPushNotification -> Encoding
toJSON :: ProcessPushNotification -> Value
$ctoJSON :: ProcessPushNotification -> Value
parseJSONList :: Value -> Parser [ProcessPushNotification]
$cparseJSONList :: Value -> Parser [ProcessPushNotification]
parseJSON :: Value -> Parser ProcessPushNotification
$cparseJSON :: Value -> Parser ProcessPushNotification
toEncodingList :: [GetPushReceiverId] -> Encoding
$ctoEncodingList :: [GetPushReceiverId] -> Encoding
toJSONList :: [GetPushReceiverId] -> Value
$ctoJSONList :: [GetPushReceiverId] -> Value
toEncoding :: GetPushReceiverId -> Encoding
$ctoEncoding :: GetPushReceiverId -> Encoding
toJSON :: GetPushReceiverId -> Value
$ctoJSON :: GetPushReceiverId -> Value
parseJSONList :: Value -> Parser [GetPushReceiverId]
$cparseJSONList :: Value -> Parser [GetPushReceiverId]
parseJSON :: Value -> Parser GetPushReceiverId
$cparseJSON :: Value -> Parser GetPushReceiverId
toEncodingList :: [GetRecentlyVisitedTMeUrls] -> Encoding
$ctoEncodingList :: [GetRecentlyVisitedTMeUrls] -> Encoding
toJSONList :: [GetRecentlyVisitedTMeUrls] -> Value
$ctoJSONList :: [GetRecentlyVisitedTMeUrls] -> Value
toEncoding :: GetRecentlyVisitedTMeUrls -> Encoding
$ctoEncoding :: GetRecentlyVisitedTMeUrls -> Encoding
toJSON :: GetRecentlyVisitedTMeUrls -> Value
$ctoJSON :: GetRecentlyVisitedTMeUrls -> Value
parseJSONList :: Value -> Parser [GetRecentlyVisitedTMeUrls]
$cparseJSONList :: Value -> Parser [GetRecentlyVisitedTMeUrls]
parseJSON :: Value -> Parser GetRecentlyVisitedTMeUrls
$cparseJSON :: Value -> Parser GetRecentlyVisitedTMeUrls
toEncodingList :: [SetUserPrivacySettingRules] -> Encoding
$ctoEncodingList :: [SetUserPrivacySettingRules] -> Encoding
toJSONList :: [SetUserPrivacySettingRules] -> Value
$ctoJSONList :: [SetUserPrivacySettingRules] -> Value
toEncoding :: SetUserPrivacySettingRules -> Encoding
$ctoEncoding :: SetUserPrivacySettingRules -> Encoding
toJSON :: SetUserPrivacySettingRules -> Value
$ctoJSON :: SetUserPrivacySettingRules -> Value
parseJSONList :: Value -> Parser [SetUserPrivacySettingRules]
$cparseJSONList :: Value -> Parser [SetUserPrivacySettingRules]
parseJSON :: Value -> Parser SetUserPrivacySettingRules
$cparseJSON :: Value -> Parser SetUserPrivacySettingRules
toEncodingList :: [GetUserPrivacySettingRules] -> Encoding
$ctoEncodingList :: [GetUserPrivacySettingRules] -> Encoding
toJSONList :: [GetUserPrivacySettingRules] -> Value
$ctoJSONList :: [GetUserPrivacySettingRules] -> Value
toEncoding :: GetUserPrivacySettingRules -> Encoding
$ctoEncoding :: GetUserPrivacySettingRules -> Encoding
toJSON :: GetUserPrivacySettingRules -> Value
$ctoJSON :: GetUserPrivacySettingRules -> Value
parseJSONList :: Value -> Parser [GetUserPrivacySettingRules]
$cparseJSONList :: Value -> Parser [GetUserPrivacySettingRules]
parseJSON :: Value -> Parser GetUserPrivacySettingRules
$cparseJSON :: Value -> Parser GetUserPrivacySettingRules
toEncodingList :: [GetOption] -> Encoding
$ctoEncodingList :: [GetOption] -> Encoding
toJSONList :: [GetOption] -> Value
$ctoJSONList :: [GetOption] -> Value
toEncoding :: GetOption -> Encoding
$ctoEncoding :: GetOption -> Encoding
toJSON :: GetOption -> Value
$ctoJSON :: GetOption -> Value
parseJSONList :: Value -> Parser [GetOption]
$cparseJSONList :: Value -> Parser [GetOption]
parseJSON :: Value -> Parser GetOption
$cparseJSON :: Value -> Parser GetOption
toEncodingList :: [SetOption] -> Encoding
$ctoEncodingList :: [SetOption] -> Encoding
toJSONList :: [SetOption] -> Value
$ctoJSONList :: [SetOption] -> Value
toEncoding :: SetOption -> Encoding
$ctoEncoding :: SetOption -> Encoding
toJSON :: SetOption -> Value
$ctoJSON :: SetOption -> Value
parseJSONList :: Value -> Parser [SetOption]
$cparseJSONList :: Value -> Parser [SetOption]
parseJSON :: Value -> Parser SetOption
$cparseJSON :: Value -> Parser SetOption
toEncodingList :: [SetAccountTtl] -> Encoding
$ctoEncodingList :: [SetAccountTtl] -> Encoding
toJSONList :: [SetAccountTtl] -> Value
$ctoJSONList :: [SetAccountTtl] -> Value
toEncoding :: SetAccountTtl -> Encoding
$ctoEncoding :: SetAccountTtl -> Encoding
toJSON :: SetAccountTtl -> Value
$ctoJSON :: SetAccountTtl -> Value
parseJSONList :: Value -> Parser [SetAccountTtl]
$cparseJSONList :: Value -> Parser [SetAccountTtl]
parseJSON :: Value -> Parser SetAccountTtl
$cparseJSON :: Value -> Parser SetAccountTtl
toEncodingList :: [GetAccountTtl] -> Encoding
$ctoEncodingList :: [GetAccountTtl] -> Encoding
toJSONList :: [GetAccountTtl] -> Value
$ctoJSONList :: [GetAccountTtl] -> Value
toEncoding :: GetAccountTtl -> Encoding
$ctoEncoding :: GetAccountTtl -> Encoding
toJSON :: GetAccountTtl -> Value
$ctoJSON :: GetAccountTtl -> Value
parseJSONList :: Value -> Parser [GetAccountTtl]
$cparseJSONList :: Value -> Parser [GetAccountTtl]
parseJSON :: Value -> Parser GetAccountTtl
$cparseJSON :: Value -> Parser GetAccountTtl
toEncodingList :: [DeleteAccount] -> Encoding
$ctoEncodingList :: [DeleteAccount] -> Encoding
toJSONList :: [DeleteAccount] -> Value
$ctoJSONList :: [DeleteAccount] -> Value
toEncoding :: DeleteAccount -> Encoding
$ctoEncoding :: DeleteAccount -> Encoding
toJSON :: DeleteAccount -> Value
$ctoJSON :: DeleteAccount -> Value
parseJSONList :: Value -> Parser [DeleteAccount]
$cparseJSONList :: Value -> Parser [DeleteAccount]
parseJSON :: Value -> Parser DeleteAccount
$cparseJSON :: Value -> Parser DeleteAccount
toEncodingList :: [RemoveChatActionBar] -> Encoding
$ctoEncodingList :: [RemoveChatActionBar] -> Encoding
toJSONList :: [RemoveChatActionBar] -> Value
$ctoJSONList :: [RemoveChatActionBar] -> Value
toEncoding :: RemoveChatActionBar -> Encoding
$ctoEncoding :: RemoveChatActionBar -> Encoding
toJSON :: RemoveChatActionBar -> Value
$ctoJSON :: RemoveChatActionBar -> Value
parseJSONList :: Value -> Parser [RemoveChatActionBar]
$cparseJSONList :: Value -> Parser [RemoveChatActionBar]
parseJSON :: Value -> Parser RemoveChatActionBar
$cparseJSON :: Value -> Parser RemoveChatActionBar
toEncodingList :: [ReportChat] -> Encoding
$ctoEncodingList :: [ReportChat] -> Encoding
toJSONList :: [ReportChat] -> Value
$ctoJSONList :: [ReportChat] -> Value
toEncoding :: ReportChat -> Encoding
$ctoEncoding :: ReportChat -> Encoding
toJSON :: ReportChat -> Value
$ctoJSON :: ReportChat -> Value
parseJSONList :: Value -> Parser [ReportChat]
$cparseJSONList :: Value -> Parser [ReportChat]
parseJSON :: Value -> Parser ReportChat
$cparseJSON :: Value -> Parser ReportChat
toEncodingList :: [GetChatStatisticsUrl] -> Encoding
$ctoEncodingList :: [GetChatStatisticsUrl] -> Encoding
toJSONList :: [GetChatStatisticsUrl] -> Value
$ctoJSONList :: [GetChatStatisticsUrl] -> Value
toEncoding :: GetChatStatisticsUrl -> Encoding
$ctoEncoding :: GetChatStatisticsUrl -> Encoding
toJSON :: GetChatStatisticsUrl -> Value
$ctoJSON :: GetChatStatisticsUrl -> Value
parseJSONList :: Value -> Parser [GetChatStatisticsUrl]
$cparseJSONList :: Value -> Parser [GetChatStatisticsUrl]
parseJSON :: Value -> Parser GetChatStatisticsUrl
$cparseJSON :: Value -> Parser GetChatStatisticsUrl
toEncodingList :: [GetChatStatistics] -> Encoding
$ctoEncodingList :: [GetChatStatistics] -> Encoding
toJSONList :: [GetChatStatistics] -> Value
$ctoJSONList :: [GetChatStatistics] -> Value
toEncoding :: GetChatStatistics -> Encoding
$ctoEncoding :: GetChatStatistics -> Encoding
toJSON :: GetChatStatistics -> Value
$ctoJSON :: GetChatStatistics -> Value
parseJSONList :: Value -> Parser [GetChatStatistics]
$cparseJSONList :: Value -> Parser [GetChatStatistics]
parseJSON :: Value -> Parser GetChatStatistics
$cparseJSON :: Value -> Parser GetChatStatistics
toEncodingList :: [GetChatStatisticsGraph] -> Encoding
$ctoEncodingList :: [GetChatStatisticsGraph] -> Encoding
toJSONList :: [GetChatStatisticsGraph] -> Value
$ctoJSONList :: [GetChatStatisticsGraph] -> Value
toEncoding :: GetChatStatisticsGraph -> Encoding
$ctoEncoding :: GetChatStatisticsGraph -> Encoding
toJSON :: GetChatStatisticsGraph -> Value
$ctoJSON :: GetChatStatisticsGraph -> Value
parseJSONList :: Value -> Parser [GetChatStatisticsGraph]
$cparseJSONList :: Value -> Parser [GetChatStatisticsGraph]
parseJSON :: Value -> Parser GetChatStatisticsGraph
$cparseJSON :: Value -> Parser GetChatStatisticsGraph
toEncodingList :: [GetStorageStatistics] -> Encoding
$ctoEncodingList :: [GetStorageStatistics] -> Encoding
toJSONList :: [GetStorageStatistics] -> Value
$ctoJSONList :: [GetStorageStatistics] -> Value
toEncoding :: GetStorageStatistics -> Encoding
$ctoEncoding :: GetStorageStatistics -> Encoding
toJSON :: GetStorageStatistics -> Value
$ctoJSON :: GetStorageStatistics -> Value
parseJSONList :: Value -> Parser [GetStorageStatistics]
$cparseJSONList :: Value -> Parser [GetStorageStatistics]
parseJSON :: Value -> Parser GetStorageStatistics
$cparseJSON :: Value -> Parser GetStorageStatistics
toEncodingList :: [GetStorageStatisticsFast] -> Encoding
$ctoEncodingList :: [GetStorageStatisticsFast] -> Encoding
toJSONList :: [GetStorageStatisticsFast] -> Value
$ctoJSONList :: [GetStorageStatisticsFast] -> Value
toEncoding :: GetStorageStatisticsFast -> Encoding
$ctoEncoding :: GetStorageStatisticsFast -> Encoding
toJSON :: GetStorageStatisticsFast -> Value
$ctoJSON :: GetStorageStatisticsFast -> Value
parseJSONList :: Value -> Parser [GetStorageStatisticsFast]
$cparseJSONList :: Value -> Parser [GetStorageStatisticsFast]
parseJSON :: Value -> Parser GetStorageStatisticsFast
$cparseJSON :: Value -> Parser GetStorageStatisticsFast
toEncodingList :: [GetDatabaseStatistics] -> Encoding
$ctoEncodingList :: [GetDatabaseStatistics] -> Encoding
toJSONList :: [GetDatabaseStatistics] -> Value
$ctoJSONList :: [GetDatabaseStatistics] -> Value
toEncoding :: GetDatabaseStatistics -> Encoding
$ctoEncoding :: GetDatabaseStatistics -> Encoding
toJSON :: GetDatabaseStatistics -> Value
$ctoJSON :: GetDatabaseStatistics -> Value
parseJSONList :: Value -> Parser [GetDatabaseStatistics]
$cparseJSONList :: Value -> Parser [GetDatabaseStatistics]
parseJSON :: Value -> Parser GetDatabaseStatistics
$cparseJSON :: Value -> Parser GetDatabaseStatistics
toEncodingList :: [OptimizeStorage] -> Encoding
$ctoEncodingList :: [OptimizeStorage] -> Encoding
toJSONList :: [OptimizeStorage] -> Value
$ctoJSONList :: [OptimizeStorage] -> Value
toEncoding :: OptimizeStorage -> Encoding
$ctoEncoding :: OptimizeStorage -> Encoding
toJSON :: OptimizeStorage -> Value
$ctoJSON :: OptimizeStorage -> Value
parseJSONList :: Value -> Parser [OptimizeStorage]
$cparseJSONList :: Value -> Parser [OptimizeStorage]
parseJSON :: Value -> Parser OptimizeStorage
$cparseJSON :: Value -> Parser OptimizeStorage
toEncodingList :: [SetNetworkType] -> Encoding
$ctoEncodingList :: [SetNetworkType] -> Encoding
toJSONList :: [SetNetworkType] -> Value
$ctoJSONList :: [SetNetworkType] -> Value
toEncoding :: SetNetworkType -> Encoding
$ctoEncoding :: SetNetworkType -> Encoding
toJSON :: SetNetworkType -> Value
$ctoJSON :: SetNetworkType -> Value
parseJSONList :: Value -> Parser [SetNetworkType]
$cparseJSONList :: Value -> Parser [SetNetworkType]
parseJSON :: Value -> Parser SetNetworkType
$cparseJSON :: Value -> Parser SetNetworkType
toEncodingList :: [GetNetworkStatistics] -> Encoding
$ctoEncodingList :: [GetNetworkStatistics] -> Encoding
toJSONList :: [GetNetworkStatistics] -> Value
$ctoJSONList :: [GetNetworkStatistics] -> Value
toEncoding :: GetNetworkStatistics -> Encoding
$ctoEncoding :: GetNetworkStatistics -> Encoding
toJSON :: GetNetworkStatistics -> Value
$ctoJSON :: GetNetworkStatistics -> Value
parseJSONList :: Value -> Parser [GetNetworkStatistics]
$cparseJSONList :: Value -> Parser [GetNetworkStatistics]
parseJSON :: Value -> Parser GetNetworkStatistics
$cparseJSON :: Value -> Parser GetNetworkStatistics
toEncodingList :: [AddNetworkStatistics] -> Encoding
$ctoEncodingList :: [AddNetworkStatistics] -> Encoding
toJSONList :: [AddNetworkStatistics] -> Value
$ctoJSONList :: [AddNetworkStatistics] -> Value
toEncoding :: AddNetworkStatistics -> Encoding
$ctoEncoding :: AddNetworkStatistics -> Encoding
toJSON :: AddNetworkStatistics -> Value
$ctoJSON :: AddNetworkStatistics -> Value
parseJSONList :: Value -> Parser [AddNetworkStatistics]
$cparseJSONList :: Value -> Parser [AddNetworkStatistics]
parseJSON :: Value -> Parser AddNetworkStatistics
$cparseJSON :: Value -> Parser AddNetworkStatistics
toEncodingList :: [ResetNetworkStatistics] -> Encoding
$ctoEncodingList :: [ResetNetworkStatistics] -> Encoding
toJSONList :: [ResetNetworkStatistics] -> Value
$ctoJSONList :: [ResetNetworkStatistics] -> Value
toEncoding :: ResetNetworkStatistics -> Encoding
$ctoEncoding :: ResetNetworkStatistics -> Encoding
toJSON :: ResetNetworkStatistics -> Value
$ctoJSON :: ResetNetworkStatistics -> Value
parseJSONList :: Value -> Parser [ResetNetworkStatistics]
$cparseJSONList :: Value -> Parser [ResetNetworkStatistics]
parseJSON :: Value -> Parser ResetNetworkStatistics
$cparseJSON :: Value -> Parser ResetNetworkStatistics
toEncodingList :: [GetAutoDownloadSettingsPresets] -> Encoding
$ctoEncodingList :: [GetAutoDownloadSettingsPresets] -> Encoding
toJSONList :: [GetAutoDownloadSettingsPresets] -> Value
$ctoJSONList :: [GetAutoDownloadSettingsPresets] -> Value
toEncoding :: GetAutoDownloadSettingsPresets -> Encoding
$ctoEncoding :: GetAutoDownloadSettingsPresets -> Encoding
toJSON :: GetAutoDownloadSettingsPresets -> Value
$ctoJSON :: GetAutoDownloadSettingsPresets -> Value
parseJSONList :: Value -> Parser [GetAutoDownloadSettingsPresets]
$cparseJSONList :: Value -> Parser [GetAutoDownloadSettingsPresets]
parseJSON :: Value -> Parser GetAutoDownloadSettingsPresets
$cparseJSON :: Value -> Parser GetAutoDownloadSettingsPresets
toEncodingList :: [SetAutoDownloadSettings] -> Encoding
$ctoEncodingList :: [SetAutoDownloadSettings] -> Encoding
toJSONList :: [SetAutoDownloadSettings] -> Value
$ctoJSONList :: [SetAutoDownloadSettings] -> Value
toEncoding :: SetAutoDownloadSettings -> Encoding
$ctoEncoding :: SetAutoDownloadSettings -> Encoding
toJSON :: SetAutoDownloadSettings -> Value
$ctoJSON :: SetAutoDownloadSettings -> Value
parseJSONList :: Value -> Parser [SetAutoDownloadSettings]
$cparseJSONList :: Value -> Parser [SetAutoDownloadSettings]
parseJSON :: Value -> Parser SetAutoDownloadSettings
$cparseJSON :: Value -> Parser SetAutoDownloadSettings
toEncodingList :: [GetBankCardInfo] -> Encoding
$ctoEncodingList :: [GetBankCardInfo] -> Encoding
toJSONList :: [GetBankCardInfo] -> Value
$ctoJSONList :: [GetBankCardInfo] -> Value
toEncoding :: GetBankCardInfo -> Encoding
$ctoEncoding :: GetBankCardInfo -> Encoding
toJSON :: GetBankCardInfo -> Value
$ctoJSON :: GetBankCardInfo -> Value
parseJSONList :: Value -> Parser [GetBankCardInfo]
$cparseJSONList :: Value -> Parser [GetBankCardInfo]
parseJSON :: Value -> Parser GetBankCardInfo
$cparseJSON :: Value -> Parser GetBankCardInfo
toEncodingList :: [GetPassportElement] -> Encoding
$ctoEncodingList :: [GetPassportElement] -> Encoding
toJSONList :: [GetPassportElement] -> Value
$ctoJSONList :: [GetPassportElement] -> Value
toEncoding :: GetPassportElement -> Encoding
$ctoEncoding :: GetPassportElement -> Encoding
toJSON :: GetPassportElement -> Value
$ctoJSON :: GetPassportElement -> Value
parseJSONList :: Value -> Parser [GetPassportElement]
$cparseJSONList :: Value -> Parser [GetPassportElement]
parseJSON :: Value -> Parser GetPassportElement
$cparseJSON :: Value -> Parser GetPassportElement
toEncodingList :: [GetAllPassportElements] -> Encoding
$ctoEncodingList :: [GetAllPassportElements] -> Encoding
toJSONList :: [GetAllPassportElements] -> Value
$ctoJSONList :: [GetAllPassportElements] -> Value
toEncoding :: GetAllPassportElements -> Encoding
$ctoEncoding :: GetAllPassportElements -> Encoding
toJSON :: GetAllPassportElements -> Value
$ctoJSON :: GetAllPassportElements -> Value
parseJSONList :: Value -> Parser [GetAllPassportElements]
$cparseJSONList :: Value -> Parser [GetAllPassportElements]
parseJSON :: Value -> Parser GetAllPassportElements
$cparseJSON :: Value -> Parser GetAllPassportElements
toEncodingList :: [SetPassportElement] -> Encoding
$ctoEncodingList :: [SetPassportElement] -> Encoding
toJSONList :: [SetPassportElement] -> Value
$ctoJSONList :: [SetPassportElement] -> Value
toEncoding :: SetPassportElement -> Encoding
$ctoEncoding :: SetPassportElement -> Encoding
toJSON :: SetPassportElement -> Value
$ctoJSON :: SetPassportElement -> Value
parseJSONList :: Value -> Parser [SetPassportElement]
$cparseJSONList :: Value -> Parser [SetPassportElement]
parseJSON :: Value -> Parser SetPassportElement
$cparseJSON :: Value -> Parser SetPassportElement
toEncodingList :: [DeletePassportElement] -> Encoding
$ctoEncodingList :: [DeletePassportElement] -> Encoding
toJSONList :: [DeletePassportElement] -> Value
$ctoJSONList :: [DeletePassportElement] -> Value
toEncoding :: DeletePassportElement -> Encoding
$ctoEncoding :: DeletePassportElement -> Encoding
toJSON :: DeletePassportElement -> Value
$ctoJSON :: DeletePassportElement -> Value
parseJSONList :: Value -> Parser [DeletePassportElement]
$cparseJSONList :: Value -> Parser [DeletePassportElement]
parseJSON :: Value -> Parser DeletePassportElement
$cparseJSON :: Value -> Parser DeletePassportElement
toEncodingList :: [SetPassportElementErrors] -> Encoding
$ctoEncodingList :: [SetPassportElementErrors] -> Encoding
toJSONList :: [SetPassportElementErrors] -> Value
$ctoJSONList :: [SetPassportElementErrors] -> Value
toEncoding :: SetPassportElementErrors -> Encoding
$ctoEncoding :: SetPassportElementErrors -> Encoding
toJSON :: SetPassportElementErrors -> Value
$ctoJSON :: SetPassportElementErrors -> Value
parseJSONList :: Value -> Parser [SetPassportElementErrors]
$cparseJSONList :: Value -> Parser [SetPassportElementErrors]
parseJSON :: Value -> Parser SetPassportElementErrors
$cparseJSON :: Value -> Parser SetPassportElementErrors
toEncodingList :: [GetPreferredCountryLanguage] -> Encoding
$ctoEncodingList :: [GetPreferredCountryLanguage] -> Encoding
toJSONList :: [GetPreferredCountryLanguage] -> Value
$ctoJSONList :: [GetPreferredCountryLanguage] -> Value
toEncoding :: GetPreferredCountryLanguage -> Encoding
$ctoEncoding :: GetPreferredCountryLanguage -> Encoding
toJSON :: GetPreferredCountryLanguage -> Value
$ctoJSON :: GetPreferredCountryLanguage -> Value
parseJSONList :: Value -> Parser [GetPreferredCountryLanguage]
$cparseJSONList :: Value -> Parser [GetPreferredCountryLanguage]
parseJSON :: Value -> Parser GetPreferredCountryLanguage
$cparseJSON :: Value -> Parser GetPreferredCountryLanguage
toEncodingList :: [SendPhoneNumberVerificationCode] -> Encoding
$ctoEncodingList :: [SendPhoneNumberVerificationCode] -> Encoding
toJSONList :: [SendPhoneNumberVerificationCode] -> Value
$ctoJSONList :: [SendPhoneNumberVerificationCode] -> Value
toEncoding :: SendPhoneNumberVerificationCode -> Encoding
$ctoEncoding :: SendPhoneNumberVerificationCode -> Encoding
toJSON :: SendPhoneNumberVerificationCode -> Value
$ctoJSON :: SendPhoneNumberVerificationCode -> Value
parseJSONList :: Value -> Parser [SendPhoneNumberVerificationCode]
$cparseJSONList :: Value -> Parser [SendPhoneNumberVerificationCode]
parseJSON :: Value -> Parser SendPhoneNumberVerificationCode
$cparseJSON :: Value -> Parser SendPhoneNumberVerificationCode
toEncodingList :: [ResendPhoneNumberVerificationCode] -> Encoding
$ctoEncodingList :: [ResendPhoneNumberVerificationCode] -> Encoding
toJSONList :: [ResendPhoneNumberVerificationCode] -> Value
$ctoJSONList :: [ResendPhoneNumberVerificationCode] -> Value
toEncoding :: ResendPhoneNumberVerificationCode -> Encoding
$ctoEncoding :: ResendPhoneNumberVerificationCode -> Encoding
toJSON :: ResendPhoneNumberVerificationCode -> Value
$ctoJSON :: ResendPhoneNumberVerificationCode -> Value
parseJSONList :: Value -> Parser [ResendPhoneNumberVerificationCode]
$cparseJSONList :: Value -> Parser [ResendPhoneNumberVerificationCode]
parseJSON :: Value -> Parser ResendPhoneNumberVerificationCode
$cparseJSON :: Value -> Parser ResendPhoneNumberVerificationCode
toEncodingList :: [CheckPhoneNumberVerificationCode] -> Encoding
$ctoEncodingList :: [CheckPhoneNumberVerificationCode] -> Encoding
toJSONList :: [CheckPhoneNumberVerificationCode] -> Value
$ctoJSONList :: [CheckPhoneNumberVerificationCode] -> Value
toEncoding :: CheckPhoneNumberVerificationCode -> Encoding
$ctoEncoding :: CheckPhoneNumberVerificationCode -> Encoding
toJSON :: CheckPhoneNumberVerificationCode -> Value
$ctoJSON :: CheckPhoneNumberVerificationCode -> Value
parseJSONList :: Value -> Parser [CheckPhoneNumberVerificationCode]
$cparseJSONList :: Value -> Parser [CheckPhoneNumberVerificationCode]
parseJSON :: Value -> Parser CheckPhoneNumberVerificationCode
$cparseJSON :: Value -> Parser CheckPhoneNumberVerificationCode
toEncodingList :: [SendEmailAddressVerificationCode] -> Encoding
$ctoEncodingList :: [SendEmailAddressVerificationCode] -> Encoding
toJSONList :: [SendEmailAddressVerificationCode] -> Value
$ctoJSONList :: [SendEmailAddressVerificationCode] -> Value
toEncoding :: SendEmailAddressVerificationCode -> Encoding
$ctoEncoding :: SendEmailAddressVerificationCode -> Encoding
toJSON :: SendEmailAddressVerificationCode -> Value
$ctoJSON :: SendEmailAddressVerificationCode -> Value
parseJSONList :: Value -> Parser [SendEmailAddressVerificationCode]
$cparseJSONList :: Value -> Parser [SendEmailAddressVerificationCode]
parseJSON :: Value -> Parser SendEmailAddressVerificationCode
$cparseJSON :: Value -> Parser SendEmailAddressVerificationCode
toEncodingList :: [ResendEmailAddressVerificationCode] -> Encoding
$ctoEncodingList :: [ResendEmailAddressVerificationCode] -> Encoding
toJSONList :: [ResendEmailAddressVerificationCode] -> Value
$ctoJSONList :: [ResendEmailAddressVerificationCode] -> Value
toEncoding :: ResendEmailAddressVerificationCode -> Encoding
$ctoEncoding :: ResendEmailAddressVerificationCode -> Encoding
toJSON :: ResendEmailAddressVerificationCode -> Value
$ctoJSON :: ResendEmailAddressVerificationCode -> Value
parseJSONList :: Value -> Parser [ResendEmailAddressVerificationCode]
$cparseJSONList :: Value -> Parser [ResendEmailAddressVerificationCode]
parseJSON :: Value -> Parser ResendEmailAddressVerificationCode
$cparseJSON :: Value -> Parser ResendEmailAddressVerificationCode
toEncodingList :: [CheckEmailAddressVerificationCode] -> Encoding
$ctoEncodingList :: [CheckEmailAddressVerificationCode] -> Encoding
toJSONList :: [CheckEmailAddressVerificationCode] -> Value
$ctoJSONList :: [CheckEmailAddressVerificationCode] -> Value
toEncoding :: CheckEmailAddressVerificationCode -> Encoding
$ctoEncoding :: CheckEmailAddressVerificationCode -> Encoding
toJSON :: CheckEmailAddressVerificationCode -> Value
$ctoJSON :: CheckEmailAddressVerificationCode -> Value
parseJSONList :: Value -> Parser [CheckEmailAddressVerificationCode]
$cparseJSONList :: Value -> Parser [CheckEmailAddressVerificationCode]
parseJSON :: Value -> Parser CheckEmailAddressVerificationCode
$cparseJSON :: Value -> Parser CheckEmailAddressVerificationCode
toEncodingList :: [GetPassportAuthorizationForm] -> Encoding
$ctoEncodingList :: [GetPassportAuthorizationForm] -> Encoding
toJSONList :: [GetPassportAuthorizationForm] -> Value
$ctoJSONList :: [GetPassportAuthorizationForm] -> Value
toEncoding :: GetPassportAuthorizationForm -> Encoding
$ctoEncoding :: GetPassportAuthorizationForm -> Encoding
toJSON :: GetPassportAuthorizationForm -> Value
$ctoJSON :: GetPassportAuthorizationForm -> Value
parseJSONList :: Value -> Parser [GetPassportAuthorizationForm]
$cparseJSONList :: Value -> Parser [GetPassportAuthorizationForm]
parseJSON :: Value -> Parser GetPassportAuthorizationForm
$cparseJSON :: Value -> Parser GetPassportAuthorizationForm
toEncodingList :: [GetPassportAuthorizationFormAvailableElements] -> Encoding
$ctoEncodingList :: [GetPassportAuthorizationFormAvailableElements] -> Encoding
toJSONList :: [GetPassportAuthorizationFormAvailableElements] -> Value
$ctoJSONList :: [GetPassportAuthorizationFormAvailableElements] -> Value
toEncoding :: GetPassportAuthorizationFormAvailableElements -> Encoding
$ctoEncoding :: GetPassportAuthorizationFormAvailableElements -> Encoding
toJSON :: GetPassportAuthorizationFormAvailableElements -> Value
$ctoJSON :: GetPassportAuthorizationFormAvailableElements -> Value
parseJSONList :: Value -> Parser [GetPassportAuthorizationFormAvailableElements]
$cparseJSONList :: Value -> Parser [GetPassportAuthorizationFormAvailableElements]
parseJSON :: Value -> Parser GetPassportAuthorizationFormAvailableElements
$cparseJSON :: Value -> Parser GetPassportAuthorizationFormAvailableElements
toEncodingList :: [SendPassportAuthorizationForm] -> Encoding
$ctoEncodingList :: [SendPassportAuthorizationForm] -> Encoding
toJSONList :: [SendPassportAuthorizationForm] -> Value
$ctoJSONList :: [SendPassportAuthorizationForm] -> Value
toEncoding :: SendPassportAuthorizationForm -> Encoding
$ctoEncoding :: SendPassportAuthorizationForm -> Encoding
toJSON :: SendPassportAuthorizationForm -> Value
$ctoJSON :: SendPassportAuthorizationForm -> Value
parseJSONList :: Value -> Parser [SendPassportAuthorizationForm]
$cparseJSONList :: Value -> Parser [SendPassportAuthorizationForm]
parseJSON :: Value -> Parser SendPassportAuthorizationForm
$cparseJSON :: Value -> Parser SendPassportAuthorizationForm
toEncodingList :: [SendPhoneNumberConfirmationCode] -> Encoding
$ctoEncodingList :: [SendPhoneNumberConfirmationCode] -> Encoding
toJSONList :: [SendPhoneNumberConfirmationCode] -> Value
$ctoJSONList :: [SendPhoneNumberConfirmationCode] -> Value
toEncoding :: SendPhoneNumberConfirmationCode -> Encoding
$ctoEncoding :: SendPhoneNumberConfirmationCode -> Encoding
toJSON :: SendPhoneNumberConfirmationCode -> Value
$ctoJSON :: SendPhoneNumberConfirmationCode -> Value
parseJSONList :: Value -> Parser [SendPhoneNumberConfirmationCode]
$cparseJSONList :: Value -> Parser [SendPhoneNumberConfirmationCode]
parseJSON :: Value -> Parser SendPhoneNumberConfirmationCode
$cparseJSON :: Value -> Parser SendPhoneNumberConfirmationCode
toEncodingList :: [ResendPhoneNumberConfirmationCode] -> Encoding
$ctoEncodingList :: [ResendPhoneNumberConfirmationCode] -> Encoding
toJSONList :: [ResendPhoneNumberConfirmationCode] -> Value
$ctoJSONList :: [ResendPhoneNumberConfirmationCode] -> Value
toEncoding :: ResendPhoneNumberConfirmationCode -> Encoding
$ctoEncoding :: ResendPhoneNumberConfirmationCode -> Encoding
toJSON :: ResendPhoneNumberConfirmationCode -> Value
$ctoJSON :: ResendPhoneNumberConfirmationCode -> Value
parseJSONList :: Value -> Parser [ResendPhoneNumberConfirmationCode]
$cparseJSONList :: Value -> Parser [ResendPhoneNumberConfirmationCode]
parseJSON :: Value -> Parser ResendPhoneNumberConfirmationCode
$cparseJSON :: Value -> Parser ResendPhoneNumberConfirmationCode
toEncodingList :: [CheckPhoneNumberConfirmationCode] -> Encoding
$ctoEncodingList :: [CheckPhoneNumberConfirmationCode] -> Encoding
toJSONList :: [CheckPhoneNumberConfirmationCode] -> Value
$ctoJSONList :: [CheckPhoneNumberConfirmationCode] -> Value
toEncoding :: CheckPhoneNumberConfirmationCode -> Encoding
$ctoEncoding :: CheckPhoneNumberConfirmationCode -> Encoding
toJSON :: CheckPhoneNumberConfirmationCode -> Value
$ctoJSON :: CheckPhoneNumberConfirmationCode -> Value
parseJSONList :: Value -> Parser [CheckPhoneNumberConfirmationCode]
$cparseJSONList :: Value -> Parser [CheckPhoneNumberConfirmationCode]
parseJSON :: Value -> Parser CheckPhoneNumberConfirmationCode
$cparseJSON :: Value -> Parser CheckPhoneNumberConfirmationCode
toEncodingList :: [SetBotUpdatesStatus] -> Encoding
$ctoEncodingList :: [SetBotUpdatesStatus] -> Encoding
toJSONList :: [SetBotUpdatesStatus] -> Value
$ctoJSONList :: [SetBotUpdatesStatus] -> Value
toEncoding :: SetBotUpdatesStatus -> Encoding
$ctoEncoding :: SetBotUpdatesStatus -> Encoding
toJSON :: SetBotUpdatesStatus -> Value
$ctoJSON :: SetBotUpdatesStatus -> Value
parseJSONList :: Value -> Parser [SetBotUpdatesStatus]
$cparseJSONList :: Value -> Parser [SetBotUpdatesStatus]
parseJSON :: Value -> Parser SetBotUpdatesStatus
$cparseJSON :: Value -> Parser SetBotUpdatesStatus
toEncodingList :: [UploadStickerFile] -> Encoding
$ctoEncodingList :: [UploadStickerFile] -> Encoding
toJSONList :: [UploadStickerFile] -> Value
$ctoJSONList :: [UploadStickerFile] -> Value
toEncoding :: UploadStickerFile -> Encoding
$ctoEncoding :: UploadStickerFile -> Encoding
toJSON :: UploadStickerFile -> Value
$ctoJSON :: UploadStickerFile -> Value
parseJSONList :: Value -> Parser [UploadStickerFile]
$cparseJSONList :: Value -> Parser [UploadStickerFile]
parseJSON :: Value -> Parser UploadStickerFile
$cparseJSON :: Value -> Parser UploadStickerFile
toEncodingList :: [CreateNewStickerSet] -> Encoding
$ctoEncodingList :: [CreateNewStickerSet] -> Encoding
toJSONList :: [CreateNewStickerSet] -> Value
$ctoJSONList :: [CreateNewStickerSet] -> Value
toEncoding :: CreateNewStickerSet -> Encoding
$ctoEncoding :: CreateNewStickerSet -> Encoding
toJSON :: CreateNewStickerSet -> Value
$ctoJSON :: CreateNewStickerSet -> Value
parseJSONList :: Value -> Parser [CreateNewStickerSet]
$cparseJSONList :: Value -> Parser [CreateNewStickerSet]
parseJSON :: Value -> Parser CreateNewStickerSet
$cparseJSON :: Value -> Parser CreateNewStickerSet
toEncodingList :: [AddStickerToSet] -> Encoding
$ctoEncodingList :: [AddStickerToSet] -> Encoding
toJSONList :: [AddStickerToSet] -> Value
$ctoJSONList :: [AddStickerToSet] -> Value
toEncoding :: AddStickerToSet -> Encoding
$ctoEncoding :: AddStickerToSet -> Encoding
toJSON :: AddStickerToSet -> Value
$ctoJSON :: AddStickerToSet -> Value
parseJSONList :: Value -> Parser [AddStickerToSet]
$cparseJSONList :: Value -> Parser [AddStickerToSet]
parseJSON :: Value -> Parser AddStickerToSet
$cparseJSON :: Value -> Parser AddStickerToSet
toEncodingList :: [SetStickerSetThumbnail] -> Encoding
$ctoEncodingList :: [SetStickerSetThumbnail] -> Encoding
toJSONList :: [SetStickerSetThumbnail] -> Value
$ctoJSONList :: [SetStickerSetThumbnail] -> Value
toEncoding :: SetStickerSetThumbnail -> Encoding
$ctoEncoding :: SetStickerSetThumbnail -> Encoding
toJSON :: SetStickerSetThumbnail -> Value
$ctoJSON :: SetStickerSetThumbnail -> Value
parseJSONList :: Value -> Parser [SetStickerSetThumbnail]
$cparseJSONList :: Value -> Parser [SetStickerSetThumbnail]
parseJSON :: Value -> Parser SetStickerSetThumbnail
$cparseJSON :: Value -> Parser SetStickerSetThumbnail
toEncodingList :: [SetStickerPositionInSet] -> Encoding
$ctoEncodingList :: [SetStickerPositionInSet] -> Encoding
toJSONList :: [SetStickerPositionInSet] -> Value
$ctoJSONList :: [SetStickerPositionInSet] -> Value
toEncoding :: SetStickerPositionInSet -> Encoding
$ctoEncoding :: SetStickerPositionInSet -> Encoding
toJSON :: SetStickerPositionInSet -> Value
$ctoJSON :: SetStickerPositionInSet -> Value
parseJSONList :: Value -> Parser [SetStickerPositionInSet]
$cparseJSONList :: Value -> Parser [SetStickerPositionInSet]
parseJSON :: Value -> Parser SetStickerPositionInSet
$cparseJSON :: Value -> Parser SetStickerPositionInSet
toEncodingList :: [RemoveStickerFromSet] -> Encoding
$ctoEncodingList :: [RemoveStickerFromSet] -> Encoding
toJSONList :: [RemoveStickerFromSet] -> Value
$ctoJSONList :: [RemoveStickerFromSet] -> Value
toEncoding :: RemoveStickerFromSet -> Encoding
$ctoEncoding :: RemoveStickerFromSet -> Encoding
toJSON :: RemoveStickerFromSet -> Value
$ctoJSON :: RemoveStickerFromSet -> Value
parseJSONList :: Value -> Parser [RemoveStickerFromSet]
$cparseJSONList :: Value -> Parser [RemoveStickerFromSet]
parseJSON :: Value -> Parser RemoveStickerFromSet
$cparseJSON :: Value -> Parser RemoveStickerFromSet
toEncodingList :: [GetMapThumbnailFile] -> Encoding
$ctoEncodingList :: [GetMapThumbnailFile] -> Encoding
toJSONList :: [GetMapThumbnailFile] -> Value
$ctoJSONList :: [GetMapThumbnailFile] -> Value
toEncoding :: GetMapThumbnailFile -> Encoding
$ctoEncoding :: GetMapThumbnailFile -> Encoding
toJSON :: GetMapThumbnailFile -> Value
$ctoJSON :: GetMapThumbnailFile -> Value
parseJSONList :: Value -> Parser [GetMapThumbnailFile]
$cparseJSONList :: Value -> Parser [GetMapThumbnailFile]
parseJSON :: Value -> Parser GetMapThumbnailFile
$cparseJSON :: Value -> Parser GetMapThumbnailFile
toEncodingList :: [AcceptTermsOfService] -> Encoding
$ctoEncodingList :: [AcceptTermsOfService] -> Encoding
toJSONList :: [AcceptTermsOfService] -> Value
$ctoJSONList :: [AcceptTermsOfService] -> Value
toEncoding :: AcceptTermsOfService -> Encoding
$ctoEncoding :: AcceptTermsOfService -> Encoding
toJSON :: AcceptTermsOfService -> Value
$ctoJSON :: AcceptTermsOfService -> Value
parseJSONList :: Value -> Parser [AcceptTermsOfService]
$cparseJSONList :: Value -> Parser [AcceptTermsOfService]
parseJSON :: Value -> Parser AcceptTermsOfService
$cparseJSON :: Value -> Parser AcceptTermsOfService
toEncodingList :: [SendCustomRequest] -> Encoding
$ctoEncodingList :: [SendCustomRequest] -> Encoding
toJSONList :: [SendCustomRequest] -> Value
$ctoJSONList :: [SendCustomRequest] -> Value
toEncoding :: SendCustomRequest -> Encoding
$ctoEncoding :: SendCustomRequest -> Encoding
toJSON :: SendCustomRequest -> Value
$ctoJSON :: SendCustomRequest -> Value
parseJSONList :: Value -> Parser [SendCustomRequest]
$cparseJSONList :: Value -> Parser [SendCustomRequest]
parseJSON :: Value -> Parser SendCustomRequest
$cparseJSON :: Value -> Parser SendCustomRequest
toEncodingList :: [AnswerCustomQuery] -> Encoding
$ctoEncodingList :: [AnswerCustomQuery] -> Encoding
toJSONList :: [AnswerCustomQuery] -> Value
$ctoJSONList :: [AnswerCustomQuery] -> Value
toEncoding :: AnswerCustomQuery -> Encoding
$ctoEncoding :: AnswerCustomQuery -> Encoding
toJSON :: AnswerCustomQuery -> Value
$ctoJSON :: AnswerCustomQuery -> Value
parseJSONList :: Value -> Parser [AnswerCustomQuery]
$cparseJSONList :: Value -> Parser [AnswerCustomQuery]
parseJSON :: Value -> Parser AnswerCustomQuery
$cparseJSON :: Value -> Parser AnswerCustomQuery
toEncodingList :: [SetAlarm] -> Encoding
$ctoEncodingList :: [SetAlarm] -> Encoding
toJSONList :: [SetAlarm] -> Value
$ctoJSONList :: [SetAlarm] -> Value
toEncoding :: SetAlarm -> Encoding
$ctoEncoding :: SetAlarm -> Encoding
toJSON :: SetAlarm -> Value
$ctoJSON :: SetAlarm -> Value
parseJSONList :: Value -> Parser [SetAlarm]
$cparseJSONList :: Value -> Parser [SetAlarm]
parseJSON :: Value -> Parser SetAlarm
$cparseJSON :: Value -> Parser SetAlarm
toEncodingList :: [GetCountryCode] -> Encoding
$ctoEncodingList :: [GetCountryCode] -> Encoding
toJSONList :: [GetCountryCode] -> Value
$ctoJSONList :: [GetCountryCode] -> Value
toEncoding :: GetCountryCode -> Encoding
$ctoEncoding :: GetCountryCode -> Encoding
toJSON :: GetCountryCode -> Value
$ctoJSON :: GetCountryCode -> Value
parseJSONList :: Value -> Parser [GetCountryCode]
$cparseJSONList :: Value -> Parser [GetCountryCode]
parseJSON :: Value -> Parser GetCountryCode
$cparseJSON :: Value -> Parser GetCountryCode
toEncodingList :: [GetInviteText] -> Encoding
$ctoEncodingList :: [GetInviteText] -> Encoding
toJSONList :: [GetInviteText] -> Value
$ctoJSONList :: [GetInviteText] -> Value
toEncoding :: GetInviteText -> Encoding
$ctoEncoding :: GetInviteText -> Encoding
toJSON :: GetInviteText -> Value
$ctoJSON :: GetInviteText -> Value
parseJSONList :: Value -> Parser [GetInviteText]
$cparseJSONList :: Value -> Parser [GetInviteText]
parseJSON :: Value -> Parser GetInviteText
$cparseJSON :: Value -> Parser GetInviteText
toEncodingList :: [GetDeepLinkInfo] -> Encoding
$ctoEncodingList :: [GetDeepLinkInfo] -> Encoding
toJSONList :: [GetDeepLinkInfo] -> Value
$ctoJSONList :: [GetDeepLinkInfo] -> Value
toEncoding :: GetDeepLinkInfo -> Encoding
$ctoEncoding :: GetDeepLinkInfo -> Encoding
toJSON :: GetDeepLinkInfo -> Value
$ctoJSON :: GetDeepLinkInfo -> Value
parseJSONList :: Value -> Parser [GetDeepLinkInfo]
$cparseJSONList :: Value -> Parser [GetDeepLinkInfo]
parseJSON :: Value -> Parser GetDeepLinkInfo
$cparseJSON :: Value -> Parser GetDeepLinkInfo
toEncodingList :: [GetApplicationConfig] -> Encoding
$ctoEncodingList :: [GetApplicationConfig] -> Encoding
toJSONList :: [GetApplicationConfig] -> Value
$ctoJSONList :: [GetApplicationConfig] -> Value
toEncoding :: GetApplicationConfig -> Encoding
$ctoEncoding :: GetApplicationConfig -> Encoding
toJSON :: GetApplicationConfig -> Value
$ctoJSON :: GetApplicationConfig -> Value
parseJSONList :: Value -> Parser [GetApplicationConfig]
$cparseJSONList :: Value -> Parser [GetApplicationConfig]
parseJSON :: Value -> Parser GetApplicationConfig
$cparseJSON :: Value -> Parser GetApplicationConfig
toEncodingList :: [SaveApplicationLogEvent] -> Encoding
$ctoEncodingList :: [SaveApplicationLogEvent] -> Encoding
toJSONList :: [SaveApplicationLogEvent] -> Value
$ctoJSONList :: [SaveApplicationLogEvent] -> Value
toEncoding :: SaveApplicationLogEvent -> Encoding
$ctoEncoding :: SaveApplicationLogEvent -> Encoding
toJSON :: SaveApplicationLogEvent -> Value
$ctoJSON :: SaveApplicationLogEvent -> Value
parseJSONList :: Value -> Parser [SaveApplicationLogEvent]
$cparseJSONList :: Value -> Parser [SaveApplicationLogEvent]
parseJSON :: Value -> Parser SaveApplicationLogEvent
$cparseJSON :: Value -> Parser SaveApplicationLogEvent
toEncodingList :: [AddProxy] -> Encoding
$ctoEncodingList :: [AddProxy] -> Encoding
toJSONList :: [AddProxy] -> Value
$ctoJSONList :: [AddProxy] -> Value
toEncoding :: AddProxy -> Encoding
$ctoEncoding :: AddProxy -> Encoding
toJSON :: AddProxy -> Value
$ctoJSON :: AddProxy -> Value
parseJSONList :: Value -> Parser [AddProxy]
$cparseJSONList :: Value -> Parser [AddProxy]
parseJSON :: Value -> Parser AddProxy
$cparseJSON :: Value -> Parser AddProxy
toEncodingList :: [EditProxy] -> Encoding
$ctoEncodingList :: [EditProxy] -> Encoding
toJSONList :: [EditProxy] -> Value
$ctoJSONList :: [EditProxy] -> Value
toEncoding :: EditProxy -> Encoding
$ctoEncoding :: EditProxy -> Encoding
toJSON :: EditProxy -> Value
$ctoJSON :: EditProxy -> Value
parseJSONList :: Value -> Parser [EditProxy]
$cparseJSONList :: Value -> Parser [EditProxy]
parseJSON :: Value -> Parser EditProxy
$cparseJSON :: Value -> Parser EditProxy
toEncodingList :: [EnableProxy] -> Encoding
$ctoEncodingList :: [EnableProxy] -> Encoding
toJSONList :: [EnableProxy] -> Value
$ctoJSONList :: [EnableProxy] -> Value
toEncoding :: EnableProxy -> Encoding
$ctoEncoding :: EnableProxy -> Encoding
toJSON :: EnableProxy -> Value
$ctoJSON :: EnableProxy -> Value
parseJSONList :: Value -> Parser [EnableProxy]
$cparseJSONList :: Value -> Parser [EnableProxy]
parseJSON :: Value -> Parser EnableProxy
$cparseJSON :: Value -> Parser EnableProxy
toEncodingList :: [DisableProxy] -> Encoding
$ctoEncodingList :: [DisableProxy] -> Encoding
toJSONList :: [DisableProxy] -> Value
$ctoJSONList :: [DisableProxy] -> Value
toEncoding :: DisableProxy -> Encoding
$ctoEncoding :: DisableProxy -> Encoding
toJSON :: DisableProxy -> Value
$ctoJSON :: DisableProxy -> Value
parseJSONList :: Value -> Parser [DisableProxy]
$cparseJSONList :: Value -> Parser [DisableProxy]
parseJSON :: Value -> Parser DisableProxy
$cparseJSON :: Value -> Parser DisableProxy
toEncodingList :: [RemoveProxy] -> Encoding
$ctoEncodingList :: [RemoveProxy] -> Encoding
toJSONList :: [RemoveProxy] -> Value
$ctoJSONList :: [RemoveProxy] -> Value
toEncoding :: RemoveProxy -> Encoding
$ctoEncoding :: RemoveProxy -> Encoding
toJSON :: RemoveProxy -> Value
$ctoJSON :: RemoveProxy -> Value
parseJSONList :: Value -> Parser [RemoveProxy]
$cparseJSONList :: Value -> Parser [RemoveProxy]
parseJSON :: Value -> Parser RemoveProxy
$cparseJSON :: Value -> Parser RemoveProxy
toEncodingList :: [GetProxies] -> Encoding
$ctoEncodingList :: [GetProxies] -> Encoding
toJSONList :: [GetProxies] -> Value
$ctoJSONList :: [GetProxies] -> Value
toEncoding :: GetProxies -> Encoding
$ctoEncoding :: GetProxies -> Encoding
toJSON :: GetProxies -> Value
$ctoJSON :: GetProxies -> Value
parseJSONList :: Value -> Parser [GetProxies]
$cparseJSONList :: Value -> Parser [GetProxies]
parseJSON :: Value -> Parser GetProxies
$cparseJSON :: Value -> Parser GetProxies
toEncodingList :: [GetProxyLink] -> Encoding
$ctoEncodingList :: [GetProxyLink] -> Encoding
toJSONList :: [GetProxyLink] -> Value
$ctoJSONList :: [GetProxyLink] -> Value
toEncoding :: GetProxyLink -> Encoding
$ctoEncoding :: GetProxyLink -> Encoding
toJSON :: GetProxyLink -> Value
$ctoJSON :: GetProxyLink -> Value
parseJSONList :: Value -> Parser [GetProxyLink]
$cparseJSONList :: Value -> Parser [GetProxyLink]
parseJSON :: Value -> Parser GetProxyLink
$cparseJSON :: Value -> Parser GetProxyLink
toEncodingList :: [PingProxy] -> Encoding
$ctoEncodingList :: [PingProxy] -> Encoding
toJSONList :: [PingProxy] -> Value
$ctoJSONList :: [PingProxy] -> Value
toEncoding :: PingProxy -> Encoding
$ctoEncoding :: PingProxy -> Encoding
toJSON :: PingProxy -> Value
$ctoJSON :: PingProxy -> Value
parseJSONList :: Value -> Parser [PingProxy]
$cparseJSONList :: Value -> Parser [PingProxy]
parseJSON :: Value -> Parser PingProxy
$cparseJSON :: Value -> Parser PingProxy
toEncodingList :: [SetLogStream] -> Encoding
$ctoEncodingList :: [SetLogStream] -> Encoding
toJSONList :: [SetLogStream] -> Value
$ctoJSONList :: [SetLogStream] -> Value
toEncoding :: SetLogStream -> Encoding
$ctoEncoding :: SetLogStream -> Encoding
toJSON :: SetLogStream -> Value
$ctoJSON :: SetLogStream -> Value
parseJSONList :: Value -> Parser [SetLogStream]
$cparseJSONList :: Value -> Parser [SetLogStream]
parseJSON :: Value -> Parser SetLogStream
$cparseJSON :: Value -> Parser SetLogStream
toEncodingList :: [GetLogStream] -> Encoding
$ctoEncodingList :: [GetLogStream] -> Encoding
toJSONList :: [GetLogStream] -> Value
$ctoJSONList :: [GetLogStream] -> Value
toEncoding :: GetLogStream -> Encoding
$ctoEncoding :: GetLogStream -> Encoding
toJSON :: GetLogStream -> Value
$ctoJSON :: GetLogStream -> Value
parseJSONList :: Value -> Parser [GetLogStream]
$cparseJSONList :: Value -> Parser [GetLogStream]
parseJSON :: Value -> Parser GetLogStream
$cparseJSON :: Value -> Parser GetLogStream
toEncodingList :: [SetLogVerbosityLevel] -> Encoding
$ctoEncodingList :: [SetLogVerbosityLevel] -> Encoding
toJSONList :: [SetLogVerbosityLevel] -> Value
$ctoJSONList :: [SetLogVerbosityLevel] -> Value
toEncoding :: SetLogVerbosityLevel -> Encoding
$ctoEncoding :: SetLogVerbosityLevel -> Encoding
toJSON :: SetLogVerbosityLevel -> Value
$ctoJSON :: SetLogVerbosityLevel -> Value
parseJSONList :: Value -> Parser [SetLogVerbosityLevel]
$cparseJSONList :: Value -> Parser [SetLogVerbosityLevel]
parseJSON :: Value -> Parser SetLogVerbosityLevel
$cparseJSON :: Value -> Parser SetLogVerbosityLevel
toEncodingList :: [GetLogVerbosityLevel] -> Encoding
$ctoEncodingList :: [GetLogVerbosityLevel] -> Encoding
toJSONList :: [GetLogVerbosityLevel] -> Value
$ctoJSONList :: [GetLogVerbosityLevel] -> Value
toEncoding :: GetLogVerbosityLevel -> Encoding
$ctoEncoding :: GetLogVerbosityLevel -> Encoding
toJSON :: GetLogVerbosityLevel -> Value
$ctoJSON :: GetLogVerbosityLevel -> Value
parseJSONList :: Value -> Parser [GetLogVerbosityLevel]
$cparseJSONList :: Value -> Parser [GetLogVerbosityLevel]
parseJSON :: Value -> Parser GetLogVerbosityLevel
$cparseJSON :: Value -> Parser GetLogVerbosityLevel
toEncodingList :: [GetLogTags] -> Encoding
$ctoEncodingList :: [GetLogTags] -> Encoding
toJSONList :: [GetLogTags] -> Value
$ctoJSONList :: [GetLogTags] -> Value
toEncoding :: GetLogTags -> Encoding
$ctoEncoding :: GetLogTags -> Encoding
toJSON :: GetLogTags -> Value
$ctoJSON :: GetLogTags -> Value
parseJSONList :: Value -> Parser [GetLogTags]
$cparseJSONList :: Value -> Parser [GetLogTags]
parseJSON :: Value -> Parser GetLogTags
$cparseJSON :: Value -> Parser GetLogTags
toEncodingList :: [SetLogTagVerbosityLevel] -> Encoding
$ctoEncodingList :: [SetLogTagVerbosityLevel] -> Encoding
toJSONList :: [SetLogTagVerbosityLevel] -> Value
$ctoJSONList :: [SetLogTagVerbosityLevel] -> Value
toEncoding :: SetLogTagVerbosityLevel -> Encoding
$ctoEncoding :: SetLogTagVerbosityLevel -> Encoding
toJSON :: SetLogTagVerbosityLevel -> Value
$ctoJSON :: SetLogTagVerbosityLevel -> Value
parseJSONList :: Value -> Parser [SetLogTagVerbosityLevel]
$cparseJSONList :: Value -> Parser [SetLogTagVerbosityLevel]
parseJSON :: Value -> Parser SetLogTagVerbosityLevel
$cparseJSON :: Value -> Parser SetLogTagVerbosityLevel
toEncodingList :: [GetLogTagVerbosityLevel] -> Encoding
$ctoEncodingList :: [GetLogTagVerbosityLevel] -> Encoding
toJSONList :: [GetLogTagVerbosityLevel] -> Value
$ctoJSONList :: [GetLogTagVerbosityLevel] -> Value
toEncoding :: GetLogTagVerbosityLevel -> Encoding
$ctoEncoding :: GetLogTagVerbosityLevel -> Encoding
toJSON :: GetLogTagVerbosityLevel -> Value
$ctoJSON :: GetLogTagVerbosityLevel -> Value
parseJSONList :: Value -> Parser [GetLogTagVerbosityLevel]
$cparseJSONList :: Value -> Parser [GetLogTagVerbosityLevel]
parseJSON :: Value -> Parser GetLogTagVerbosityLevel
$cparseJSON :: Value -> Parser GetLogTagVerbosityLevel
toEncodingList :: [AddLogMessage] -> Encoding
$ctoEncodingList :: [AddLogMessage] -> Encoding
toJSONList :: [AddLogMessage] -> Value
$ctoJSONList :: [AddLogMessage] -> Value
toEncoding :: AddLogMessage -> Encoding
$ctoEncoding :: AddLogMessage -> Encoding
toJSON :: AddLogMessage -> Value
$ctoJSON :: AddLogMessage -> Value
parseJSONList :: Value -> Parser [AddLogMessage]
$cparseJSONList :: Value -> Parser [AddLogMessage]
parseJSON :: Value -> Parser AddLogMessage
$cparseJSON :: Value -> Parser AddLogMessage
toEncodingList :: [TestCallEmpty] -> Encoding
$ctoEncodingList :: [TestCallEmpty] -> Encoding
toJSONList :: [TestCallEmpty] -> Value
$ctoJSONList :: [TestCallEmpty] -> Value
toEncoding :: TestCallEmpty -> Encoding
$ctoEncoding :: TestCallEmpty -> Encoding
toJSON :: TestCallEmpty -> Value
$ctoJSON :: TestCallEmpty -> Value
parseJSONList :: Value -> Parser [TestCallEmpty]
$cparseJSONList :: Value -> Parser [TestCallEmpty]
parseJSON :: Value -> Parser TestCallEmpty
$cparseJSON :: Value -> Parser TestCallEmpty
toEncodingList :: [TestCallString] -> Encoding
$ctoEncodingList :: [TestCallString] -> Encoding
toJSONList :: [TestCallString] -> Value
$ctoJSONList :: [TestCallString] -> Value
toEncoding :: TestCallString -> Encoding
$ctoEncoding :: TestCallString -> Encoding
toJSON :: TestCallString -> Value
$ctoJSON :: TestCallString -> Value
parseJSONList :: Value -> Parser [TestCallString]
$cparseJSONList :: Value -> Parser [TestCallString]
parseJSON :: Value -> Parser TestCallString
$cparseJSON :: Value -> Parser TestCallString
toEncodingList :: [TestCallBytes] -> Encoding
$ctoEncodingList :: [TestCallBytes] -> Encoding
toJSONList :: [TestCallBytes] -> Value
$ctoJSONList :: [TestCallBytes] -> Value
toEncoding :: TestCallBytes -> Encoding
$ctoEncoding :: TestCallBytes -> Encoding
toJSON :: TestCallBytes -> Value
$ctoJSON :: TestCallBytes -> Value
parseJSONList :: Value -> Parser [TestCallBytes]
$cparseJSONList :: Value -> Parser [TestCallBytes]
parseJSON :: Value -> Parser TestCallBytes
$cparseJSON :: Value -> Parser TestCallBytes
toEncodingList :: [TestCallVectorInt] -> Encoding
$ctoEncodingList :: [TestCallVectorInt] -> Encoding
toJSONList :: [TestCallVectorInt] -> Value
$ctoJSONList :: [TestCallVectorInt] -> Value
toEncoding :: TestCallVectorInt -> Encoding
$ctoEncoding :: TestCallVectorInt -> Encoding
toJSON :: TestCallVectorInt -> Value
$ctoJSON :: TestCallVectorInt -> Value
parseJSONList :: Value -> Parser [TestCallVectorInt]
$cparseJSONList :: Value -> Parser [TestCallVectorInt]
parseJSON :: Value -> Parser TestCallVectorInt
$cparseJSON :: Value -> Parser TestCallVectorInt
toEncodingList :: [TestCallVectorIntObject] -> Encoding
$ctoEncodingList :: [TestCallVectorIntObject] -> Encoding
toJSONList :: [TestCallVectorIntObject] -> Value
$ctoJSONList :: [TestCallVectorIntObject] -> Value
toEncoding :: TestCallVectorIntObject -> Encoding
$ctoEncoding :: TestCallVectorIntObject -> Encoding
toJSON :: TestCallVectorIntObject -> Value
$ctoJSON :: TestCallVectorIntObject -> Value
parseJSONList :: Value -> Parser [TestCallVectorIntObject]
$cparseJSONList :: Value -> Parser [TestCallVectorIntObject]
parseJSON :: Value -> Parser TestCallVectorIntObject
$cparseJSON :: Value -> Parser TestCallVectorIntObject
toEncodingList :: [TestCallVectorString] -> Encoding
$ctoEncodingList :: [TestCallVectorString] -> Encoding
toJSONList :: [TestCallVectorString] -> Value
$ctoJSONList :: [TestCallVectorString] -> Value
toEncoding :: TestCallVectorString -> Encoding
$ctoEncoding :: TestCallVectorString -> Encoding
toJSON :: TestCallVectorString -> Value
$ctoJSON :: TestCallVectorString -> Value
parseJSONList :: Value -> Parser [TestCallVectorString]
$cparseJSONList :: Value -> Parser [TestCallVectorString]
parseJSON :: Value -> Parser TestCallVectorString
$cparseJSON :: Value -> Parser TestCallVectorString
toEncodingList :: [TestCallVectorStringObject] -> Encoding
$ctoEncodingList :: [TestCallVectorStringObject] -> Encoding
toJSONList :: [TestCallVectorStringObject] -> Value
$ctoJSONList :: [TestCallVectorStringObject] -> Value
toEncoding :: TestCallVectorStringObject -> Encoding
$ctoEncoding :: TestCallVectorStringObject -> Encoding
toJSON :: TestCallVectorStringObject -> Value
$ctoJSON :: TestCallVectorStringObject -> Value
parseJSONList :: Value -> Parser [TestCallVectorStringObject]
$cparseJSONList :: Value -> Parser [TestCallVectorStringObject]
parseJSON :: Value -> Parser TestCallVectorStringObject
$cparseJSON :: Value -> Parser TestCallVectorStringObject
toEncodingList :: [TestSquareInt] -> Encoding
$ctoEncodingList :: [TestSquareInt] -> Encoding
toJSONList :: [TestSquareInt] -> Value
$ctoJSONList :: [TestSquareInt] -> Value
toEncoding :: TestSquareInt -> Encoding
$ctoEncoding :: TestSquareInt -> Encoding
toJSON :: TestSquareInt -> Value
$ctoJSON :: TestSquareInt -> Value
parseJSONList :: Value -> Parser [TestSquareInt]
$cparseJSONList :: Value -> Parser [TestSquareInt]
parseJSON :: Value -> Parser TestSquareInt
$cparseJSON :: Value -> Parser TestSquareInt
toEncodingList :: [TestNetwork] -> Encoding
$ctoEncodingList :: [TestNetwork] -> Encoding
toJSONList :: [TestNetwork] -> Value
$ctoJSONList :: [TestNetwork] -> Value
toEncoding :: TestNetwork -> Encoding
$ctoEncoding :: TestNetwork -> Encoding
toJSON :: TestNetwork -> Value
$ctoJSON :: TestNetwork -> Value
parseJSONList :: Value -> Parser [TestNetwork]
$cparseJSONList :: Value -> Parser [TestNetwork]
parseJSON :: Value -> Parser TestNetwork
$cparseJSON :: Value -> Parser TestNetwork
toEncodingList :: [TestProxy] -> Encoding
$ctoEncodingList :: [TestProxy] -> Encoding
toJSONList :: [TestProxy] -> Value
$ctoJSONList :: [TestProxy] -> Value
toEncoding :: TestProxy -> Encoding
$ctoEncoding :: TestProxy -> Encoding
toJSON :: TestProxy -> Value
$ctoJSON :: TestProxy -> Value
parseJSONList :: Value -> Parser [TestProxy]
$cparseJSONList :: Value -> Parser [TestProxy]
parseJSON :: Value -> Parser TestProxy
$cparseJSON :: Value -> Parser TestProxy
toEncodingList :: [TestGetDifference] -> Encoding
$ctoEncodingList :: [TestGetDifference] -> Encoding
toJSONList :: [TestGetDifference] -> Value
$ctoJSONList :: [TestGetDifference] -> Value
toEncoding :: TestGetDifference -> Encoding
$ctoEncoding :: TestGetDifference -> Encoding
toJSON :: TestGetDifference -> Value
$ctoJSON :: TestGetDifference -> Value
parseJSONList :: Value -> Parser [TestGetDifference]
$cparseJSONList :: Value -> Parser [TestGetDifference]
parseJSON :: Value -> Parser TestGetDifference
$cparseJSON :: Value -> Parser TestGetDifference
toEncodingList :: [TestUseUpdate] -> Encoding
$ctoEncodingList :: [TestUseUpdate] -> Encoding
toJSONList :: [TestUseUpdate] -> Value
$ctoJSONList :: [TestUseUpdate] -> Value
toEncoding :: TestUseUpdate -> Encoding
$ctoEncoding :: TestUseUpdate -> Encoding
toJSON :: TestUseUpdate -> Value
$ctoJSON :: TestUseUpdate -> Value
parseJSONList :: Value -> Parser [TestUseUpdate]
$cparseJSONList :: Value -> Parser [TestUseUpdate]
parseJSON :: Value -> Parser TestUseUpdate
$cparseJSON :: Value -> Parser TestUseUpdate
toEncodingList :: [TestReturnError] -> Encoding
$ctoEncodingList :: [TestReturnError] -> Encoding
toJSONList :: [TestReturnError] -> Value
$ctoJSONList :: [TestReturnError] -> Value
toEncoding :: TestReturnError -> Encoding
$ctoEncoding :: TestReturnError -> Encoding
toJSON :: TestReturnError -> Value
$ctoJSON :: TestReturnError -> Value
parseJSONList :: Value -> Parser [TestReturnError]
$cparseJSONList :: Value -> Parser [TestReturnError]
parseJSON :: Value -> Parser TestReturnError
$cparseJSON :: Value -> Parser TestReturnError
instancesDec'