{-# LANGUAGE TypeOperators #-}
-- | TD API functions (methods) generated by tdlib-gen

module TDLib.Generated.Functions where

import Data.ByteString.Base64.Type
import Language.TL.I64
import Polysemy
import TDLib.Effect
import TDLib.Generated.FunArgs
import TDLib.Generated.Types
import TDLib.Types.Common


-- | Returns the current authorization state; this is an offline request. For informational purposes only. Use updateAuthorizationState instead to maintain the current authorization state
getAuthorizationState ::
  Member TDLib r =>
  Sem r (Error  AuthorizationState)
getAuthorizationState :: Sem r (Error ∪ AuthorizationState)
getAuthorizationState  = GetAuthorizationState -> Sem r (Error ∪ AuthorizationState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetAuthorizationState -> Sem r (Error ∪ AuthorizationState))
-> GetAuthorizationState -> Sem r (Error ∪ AuthorizationState)
forall a b. (a -> b) -> a -> b
$ GetAuthorizationState
GetAuthorizationState 
-- | Sets the parameters for TDLib initialization. Works only when the current authorization state is authorizationStateWaitTdlibParameters 
setTdlibParameters ::
  Member TDLib r =>
  -- | Parameters
  TdlibParameters ->
  Sem r (Error  Ok)
setTdlibParameters :: TdlibParameters -> Sem r (Error ∪ Ok)
setTdlibParameters _1 :: TdlibParameters
_1 = SetTdlibParameters -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetTdlibParameters -> Sem r (Error ∪ Ok))
-> SetTdlibParameters -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TdlibParameters -> SetTdlibParameters
SetTdlibParameters TdlibParameters
_1
-- | Checks the database encryption key for correctness. Works only when the current authorization state is authorizationStateWaitEncryptionKey 
checkDatabaseEncryptionKey ::
  Member TDLib r =>
  -- | Encryption key to check or set up
  ByteString64 ->
  Sem r (Error  Ok)
checkDatabaseEncryptionKey :: ByteString64 -> Sem r (Error ∪ Ok)
checkDatabaseEncryptionKey _1 :: ByteString64
_1 = CheckDatabaseEncryptionKey -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckDatabaseEncryptionKey -> Sem r (Error ∪ Ok))
-> CheckDatabaseEncryptionKey -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ByteString64 -> CheckDatabaseEncryptionKey
CheckDatabaseEncryptionKey ByteString64
_1
-- | 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 ::
  Member TDLib r =>
  -- | The phone number of the user, in international format 
  T ->
  -- | Settings for the authentication of the user's phone number
  PhoneNumberAuthenticationSettings ->
  Sem r (Error  Ok)
setAuthenticationPhoneNumber :: T -> PhoneNumberAuthenticationSettings -> Sem r (Error ∪ Ok)
setAuthenticationPhoneNumber _1 :: T
_1 _2 :: PhoneNumberAuthenticationSettings
_2 = SetAuthenticationPhoneNumber -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetAuthenticationPhoneNumber -> Sem r (Error ∪ Ok))
-> SetAuthenticationPhoneNumber -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T
-> PhoneNumberAuthenticationSettings
-> SetAuthenticationPhoneNumber
SetAuthenticationPhoneNumber T
_1 PhoneNumberAuthenticationSettings
_2
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
resendAuthenticationCode :: Sem r (Error ∪ Ok)
resendAuthenticationCode  = ResendAuthenticationCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendAuthenticationCode -> Sem r (Error ∪ Ok))
-> ResendAuthenticationCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ResendAuthenticationCode
ResendAuthenticationCode 
-- | Checks the authentication code. Works only when the current authorization state is authorizationStateWaitCode 
checkAuthenticationCode ::
  Member TDLib r =>
  -- | The verification code received via SMS, Telegram message, phone call, or flash call
  T ->
  Sem r (Error  Ok)
checkAuthenticationCode :: T -> Sem r (Error ∪ Ok)
checkAuthenticationCode _1 :: T
_1 = CheckAuthenticationCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckAuthenticationCode -> Sem r (Error ∪ Ok))
-> CheckAuthenticationCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckAuthenticationCode
CheckAuthenticationCode T
_1
-- | Requests QR code authentication by scanning a QR code on another logged in device. Works only when the current authorization state is authorizationStateWaitPhoneNumber,
requestQrCodeAuthentication ::
  Member TDLib r =>
  -- | List of user identifiers of other users currently using the client
  [I32] ->
  Sem r (Error  Ok)
requestQrCodeAuthentication :: [I32] -> Sem r (Error ∪ Ok)
requestQrCodeAuthentication _1 :: [I32]
_1 = RequestQrCodeAuthentication -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RequestQrCodeAuthentication -> Sem r (Error ∪ Ok))
-> RequestQrCodeAuthentication -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ [I32] -> RequestQrCodeAuthentication
RequestQrCodeAuthentication [I32]
_1
-- | Finishes user registration. Works only when the current authorization state is authorizationStateWaitRegistration
registerUser ::
  Member TDLib r =>
  -- | The first name of the user; 1-64 characters 
  T ->
  -- | The last name of the user; 0-64 characters
  T ->
  Sem r (Error  Ok)
registerUser :: T -> T -> Sem r (Error ∪ Ok)
registerUser _1 :: T
_1 _2 :: T
_2 = RegisterUser -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RegisterUser -> Sem r (Error ∪ Ok))
-> RegisterUser -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> T -> RegisterUser
RegisterUser T
_1 T
_2
-- | Checks the authentication password for correctness. Works only when the current authorization state is authorizationStateWaitPassword 
checkAuthenticationPassword ::
  Member TDLib r =>
  -- | The password to check
  T ->
  Sem r (Error  Ok)
checkAuthenticationPassword :: T -> Sem r (Error ∪ Ok)
checkAuthenticationPassword _1 :: T
_1 = CheckAuthenticationPassword -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckAuthenticationPassword -> Sem r (Error ∪ Ok))
-> CheckAuthenticationPassword -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckAuthenticationPassword
CheckAuthenticationPassword T
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
requestAuthenticationPasswordRecovery :: Sem r (Error ∪ Ok)
requestAuthenticationPasswordRecovery  = RequestAuthenticationPasswordRecovery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RequestAuthenticationPasswordRecovery -> Sem r (Error ∪ Ok))
-> RequestAuthenticationPasswordRecovery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ RequestAuthenticationPasswordRecovery
RequestAuthenticationPasswordRecovery 
-- | 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 ::
  Member TDLib r =>
  -- | Recovery code to check
  T ->
  Sem r (Error  Ok)
recoverAuthenticationPassword :: T -> Sem r (Error ∪ Ok)
recoverAuthenticationPassword _1 :: T
_1 = RecoverAuthenticationPassword -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RecoverAuthenticationPassword -> Sem r (Error ∪ Ok))
-> RecoverAuthenticationPassword -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> RecoverAuthenticationPassword
RecoverAuthenticationPassword T
_1
-- | 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 ::
  Member TDLib r =>
  -- | The bot token
  T ->
  Sem r (Error  Ok)
checkAuthenticationBotToken :: T -> Sem r (Error ∪ Ok)
checkAuthenticationBotToken _1 :: T
_1 = CheckAuthenticationBotToken -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckAuthenticationBotToken -> Sem r (Error ∪ Ok))
-> CheckAuthenticationBotToken -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckAuthenticationBotToken
CheckAuthenticationBotToken T
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
logOut :: Sem r (Error ∪ Ok)
logOut  = LogOut -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (LogOut -> Sem r (Error ∪ Ok)) -> LogOut -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ LogOut
LogOut 
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
close :: Sem r (Error ∪ Ok)
close  = Close -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (Close -> Sem r (Error ∪ Ok)) -> Close -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Close
Close 
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
destroy :: Sem r (Error ∪ Ok)
destroy  = Destroy -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (Destroy -> Sem r (Error ∪ Ok)) -> Destroy -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Destroy
Destroy 
-- | Confirms QR code authentication on another device. Returns created session on success 
confirmQrCodeAuthentication ::
  Member TDLib r =>
  -- | A link from a QR code. The link must be scanned by the in-app camera
  T ->
  Sem r (Error  Session)
confirmQrCodeAuthentication :: T -> Sem r (Error ∪ Session)
confirmQrCodeAuthentication _1 :: T
_1 = ConfirmQrCodeAuthentication -> Sem r (Error ∪ Session)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ConfirmQrCodeAuthentication -> Sem r (Error ∪ Session))
-> ConfirmQrCodeAuthentication -> Sem r (Error ∪ Session)
forall a b. (a -> b) -> a -> b
$ T -> ConfirmQrCodeAuthentication
ConfirmQrCodeAuthentication T
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Updates)
getCurrentState :: Sem r (Error ∪ Updates)
getCurrentState  = GetCurrentState -> Sem r (Error ∪ Updates)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetCurrentState -> Sem r (Error ∪ Updates))
-> GetCurrentState -> Sem r (Error ∪ Updates)
forall a b. (a -> b) -> a -> b
$ GetCurrentState
GetCurrentState 
-- | Changes the database encryption key. Usually the encryption key is never changed and is stored in some OS keychain 
setDatabaseEncryptionKey ::
  Member TDLib r =>
  -- | New encryption key
  ByteString64 ->
  Sem r (Error  Ok)
setDatabaseEncryptionKey :: ByteString64 -> Sem r (Error ∪ Ok)
setDatabaseEncryptionKey _1 :: ByteString64
_1 = SetDatabaseEncryptionKey -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetDatabaseEncryptionKey -> Sem r (Error ∪ Ok))
-> SetDatabaseEncryptionKey -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ByteString64 -> SetDatabaseEncryptionKey
SetDatabaseEncryptionKey ByteString64
_1
-- | Returns the current state of 2-step verification
getPasswordState ::
  Member TDLib r =>
  Sem r (Error  PasswordState)
getPasswordState :: Sem r (Error ∪ PasswordState)
getPasswordState  = GetPasswordState -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPasswordState -> Sem r (Error ∪ PasswordState))
-> GetPasswordState -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ GetPasswordState
GetPasswordState 
-- | 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 ::
  Member TDLib r =>
  -- | Previous password of the user 
  T ->
  -- | New password of the user; may be empty to remove the password 
  T ->
  -- | New password hint; may be empty 
  T ->
  -- | Pass true if the recovery email address should be changed 
  Bool ->
  -- | New recovery email address; may be empty
  T ->
  Sem r (Error  PasswordState)
setPassword :: T -> T -> T -> Bool -> T -> Sem r (Error ∪ PasswordState)
setPassword _1 :: T
_1 _2 :: T
_2 _3 :: T
_3 _4 :: Bool
_4 _5 :: T
_5 = SetPassword -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetPassword -> Sem r (Error ∪ PasswordState))
-> SetPassword -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ T -> T -> T -> Bool -> T -> SetPassword
SetPassword T
_1 T
_2 T
_3 Bool
_4 T
_5
-- | 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 ::
  Member TDLib r =>
  -- | The password for the current user
  T ->
  Sem r (Error  RecoveryEmailAddress)
getRecoveryEmailAddress :: T -> Sem r (Error ∪ RecoveryEmailAddress)
getRecoveryEmailAddress _1 :: T
_1 = GetRecoveryEmailAddress -> Sem r (Error ∪ RecoveryEmailAddress)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRecoveryEmailAddress -> Sem r (Error ∪ RecoveryEmailAddress))
-> GetRecoveryEmailAddress -> Sem r (Error ∪ RecoveryEmailAddress)
forall a b. (a -> b) -> a -> b
$ T -> GetRecoveryEmailAddress
GetRecoveryEmailAddress T
_1
-- | 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 ::
  Member TDLib r =>
  T ->
  T ->
  Sem r (Error  PasswordState)
setRecoveryEmailAddress :: T -> T -> Sem r (Error ∪ PasswordState)
setRecoveryEmailAddress _1 :: T
_1 _2 :: T
_2 = SetRecoveryEmailAddress -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetRecoveryEmailAddress -> Sem r (Error ∪ PasswordState))
-> SetRecoveryEmailAddress -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ T -> T -> SetRecoveryEmailAddress
SetRecoveryEmailAddress T
_1 T
_2
-- | Checks the 2-step verification recovery email address verification code 
checkRecoveryEmailAddressCode ::
  Member TDLib r =>
  -- | Verification code
  T ->
  Sem r (Error  PasswordState)
checkRecoveryEmailAddressCode :: T -> Sem r (Error ∪ PasswordState)
checkRecoveryEmailAddressCode _1 :: T
_1 = CheckRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState))
-> CheckRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ T -> CheckRecoveryEmailAddressCode
CheckRecoveryEmailAddressCode T
_1
-- | Resends the 2-step verification recovery email address verification code
resendRecoveryEmailAddressCode ::
  Member TDLib r =>
  Sem r (Error  PasswordState)
resendRecoveryEmailAddressCode :: Sem r (Error ∪ PasswordState)
resendRecoveryEmailAddressCode  = ResendRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState))
-> ResendRecoveryEmailAddressCode -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ ResendRecoveryEmailAddressCode
ResendRecoveryEmailAddressCode 
-- | Requests to send a password recovery code to an email address that was previously set up
requestPasswordRecovery ::
  Member TDLib r =>
  Sem r (Error  EmailAddressAuthenticationCodeInfo)
requestPasswordRecovery :: Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
requestPasswordRecovery  = RequestPasswordRecovery
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RequestPasswordRecovery
 -> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo))
-> RequestPasswordRecovery
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ RequestPasswordRecovery
RequestPasswordRecovery 
-- | Recovers the password using a recovery code sent to an email address that was previously set up 
recoverPassword ::
  Member TDLib r =>
  -- | Recovery code to check
  T ->
  Sem r (Error  PasswordState)
recoverPassword :: T -> Sem r (Error ∪ PasswordState)
recoverPassword _1 :: T
_1 = RecoverPassword -> Sem r (Error ∪ PasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RecoverPassword -> Sem r (Error ∪ PasswordState))
-> RecoverPassword -> Sem r (Error ∪ PasswordState)
forall a b. (a -> b) -> a -> b
$ T -> RecoverPassword
RecoverPassword T
_1
-- | Creates a new temporary password for processing payments 
createTemporaryPassword ::
  Member TDLib r =>
  -- | Persistent user password 
  T ->
  -- | Time during which the temporary password will be valid, in seconds; should be between 60 and 86400
  I32 ->
  Sem r (Error  TemporaryPasswordState)
createTemporaryPassword :: T -> I32 -> Sem r (Error ∪ TemporaryPasswordState)
createTemporaryPassword _1 :: T
_1 _2 :: I32
_2 = CreateTemporaryPassword -> Sem r (Error ∪ TemporaryPasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateTemporaryPassword -> Sem r (Error ∪ TemporaryPasswordState))
-> CreateTemporaryPassword
-> Sem r (Error ∪ TemporaryPasswordState)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> CreateTemporaryPassword
CreateTemporaryPassword T
_1 I32
_2
-- | Returns information about the current temporary password
getTemporaryPasswordState ::
  Member TDLib r =>
  Sem r (Error  TemporaryPasswordState)
getTemporaryPasswordState :: Sem r (Error ∪ TemporaryPasswordState)
getTemporaryPasswordState  = GetTemporaryPasswordState -> Sem r (Error ∪ TemporaryPasswordState)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetTemporaryPasswordState
 -> Sem r (Error ∪ TemporaryPasswordState))
-> GetTemporaryPasswordState
-> Sem r (Error ∪ TemporaryPasswordState)
forall a b. (a -> b) -> a -> b
$ GetTemporaryPasswordState
GetTemporaryPasswordState 
-- | Returns the current user
getMe ::
  Member TDLib r =>
  Sem r (Error  User)
getMe :: Sem r (Error ∪ User)
getMe  = GetMe -> Sem r (Error ∪ User)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMe -> Sem r (Error ∪ User)) -> GetMe -> Sem r (Error ∪ User)
forall a b. (a -> b) -> a -> b
$ GetMe
GetMe 
-- | Returns information about a user by their identifier. This is an offline request if the current user is not a bot 
getUser ::
  Member TDLib r =>
  -- | User identifier
  I32 ->
  Sem r (Error  User)
getUser :: I32 -> Sem r (Error ∪ User)
getUser _1 :: I32
_1 = GetUser -> Sem r (Error ∪ User)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetUser -> Sem r (Error ∪ User))
-> GetUser -> Sem r (Error ∪ User)
forall a b. (a -> b) -> a -> b
$ I32 -> GetUser
GetUser I32
_1
-- | Returns full information about a user by their identifier 
getUserFullInfo ::
  Member TDLib r =>
  -- | User identifier
  I32 ->
  Sem r (Error  UserFullInfo)
getUserFullInfo :: I32 -> Sem r (Error ∪ UserFullInfo)
getUserFullInfo _1 :: I32
_1 = GetUserFullInfo -> Sem r (Error ∪ UserFullInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetUserFullInfo -> Sem r (Error ∪ UserFullInfo))
-> GetUserFullInfo -> Sem r (Error ∪ UserFullInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> GetUserFullInfo
GetUserFullInfo I32
_1
-- | Returns information about a basic group by its identifier. This is an offline request if the current user is not a bot 
getBasicGroup ::
  Member TDLib r =>
  -- | Basic group identifier
  I32 ->
  Sem r (Error  BasicGroup)
getBasicGroup :: I32 -> Sem r (Error ∪ BasicGroup)
getBasicGroup _1 :: I32
_1 = GetBasicGroup -> Sem r (Error ∪ BasicGroup)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBasicGroup -> Sem r (Error ∪ BasicGroup))
-> GetBasicGroup -> Sem r (Error ∪ BasicGroup)
forall a b. (a -> b) -> a -> b
$ I32 -> GetBasicGroup
GetBasicGroup I32
_1
-- | Returns full information about a basic group by its identifier 
getBasicGroupFullInfo ::
  Member TDLib r =>
  -- | Basic group identifier
  I32 ->
  Sem r (Error  BasicGroupFullInfo)
getBasicGroupFullInfo :: I32 -> Sem r (Error ∪ BasicGroupFullInfo)
getBasicGroupFullInfo _1 :: I32
_1 = GetBasicGroupFullInfo -> Sem r (Error ∪ BasicGroupFullInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBasicGroupFullInfo -> Sem r (Error ∪ BasicGroupFullInfo))
-> GetBasicGroupFullInfo -> Sem r (Error ∪ BasicGroupFullInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> GetBasicGroupFullInfo
GetBasicGroupFullInfo I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Supergroup or channel identifier
  I32 ->
  Sem r (Error  Supergroup)
getSupergroup :: I32 -> Sem r (Error ∪ Supergroup)
getSupergroup _1 :: I32
_1 = GetSupergroup -> Sem r (Error ∪ Supergroup)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSupergroup -> Sem r (Error ∪ Supergroup))
-> GetSupergroup -> Sem r (Error ∪ Supergroup)
forall a b. (a -> b) -> a -> b
$ I32 -> GetSupergroup
GetSupergroup I32
_1
-- | Returns full information about a supergroup or a channel by its identifier, cached for up to 1 minute 
getSupergroupFullInfo ::
  Member TDLib r =>
  -- | Supergroup or channel identifier
  I32 ->
  Sem r (Error  SupergroupFullInfo)
getSupergroupFullInfo :: I32 -> Sem r (Error ∪ SupergroupFullInfo)
getSupergroupFullInfo _1 :: I32
_1 = GetSupergroupFullInfo -> Sem r (Error ∪ SupergroupFullInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSupergroupFullInfo -> Sem r (Error ∪ SupergroupFullInfo))
-> GetSupergroupFullInfo -> Sem r (Error ∪ SupergroupFullInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> GetSupergroupFullInfo
GetSupergroupFullInfo I32
_1
-- | Returns information about a secret chat by its identifier. This is an offline request 
getSecretChat ::
  Member TDLib r =>
  -- | Secret chat identifier
  I32 ->
  Sem r (Error  SecretChat)
getSecretChat :: I32 -> Sem r (Error ∪ SecretChat)
getSecretChat _1 :: I32
_1 = GetSecretChat -> Sem r (Error ∪ SecretChat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSecretChat -> Sem r (Error ∪ SecretChat))
-> GetSecretChat -> Sem r (Error ∪ SecretChat)
forall a b. (a -> b) -> a -> b
$ I32 -> GetSecretChat
GetSecretChat I32
_1
-- | Returns information about a chat by its identifier, this is an offline request if the current user is not a bot 
getChat ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Chat)
getChat :: I32 -> Sem r (Error ∪ Chat)
getChat _1 :: I32
_1 = GetChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChat -> Sem r (Error ∪ Chat))
-> GetChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChat
GetChat I32
_1
-- | Returns information about a message 
getMessage ::
  Member TDLib r =>
  -- | Identifier of the chat the message belongs to 
  I53 ->
  -- | Identifier of the message to get
  I53 ->
  Sem r (Error  Message)
getMessage :: I32 -> I32 -> Sem r (Error ∪ Message)
getMessage _1 :: I32
_1 _2 :: I32
_2 = GetMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMessage -> Sem r (Error ∪ Message))
-> GetMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetMessage
GetMessage I32
_1 I32
_2
-- | Returns information about a message, if it is available locally without sending network request. This is an offline request 
getMessageLocally ::
  Member TDLib r =>
  -- | Identifier of the chat the message belongs to 
  I53 ->
  -- | Identifier of the message to get
  I53 ->
  Sem r (Error  Message)
getMessageLocally :: I32 -> I32 -> Sem r (Error ∪ Message)
getMessageLocally _1 :: I32
_1 _2 :: I32
_2 = GetMessageLocally -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMessageLocally -> Sem r (Error ∪ Message))
-> GetMessageLocally -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetMessageLocally
GetMessageLocally I32
_1 I32
_2
-- | Returns information about a message that is replied by given message 
getRepliedMessage ::
  Member TDLib r =>
  -- | Identifier of the chat the message belongs to 
  I53 ->
  -- | Identifier of the message reply to which get
  I53 ->
  Sem r (Error  Message)
getRepliedMessage :: I32 -> I32 -> Sem r (Error ∪ Message)
getRepliedMessage _1 :: I32
_1 _2 :: I32
_2 = GetRepliedMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRepliedMessage -> Sem r (Error ∪ Message))
-> GetRepliedMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetRepliedMessage
GetRepliedMessage I32
_1 I32
_2
-- | Returns information about a pinned chat message 
getChatPinnedMessage ::
  Member TDLib r =>
  -- | Identifier of the chat the message belongs to
  I53 ->
  Sem r (Error  Message)
getChatPinnedMessage :: I32 -> Sem r (Error ∪ Message)
getChatPinnedMessage _1 :: I32
_1 = GetChatPinnedMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatPinnedMessage -> Sem r (Error ∪ Message))
-> GetChatPinnedMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChatPinnedMessage
GetChatPinnedMessage I32
_1
-- | Returns information about messages. If a message is not found, returns null on the corresponding position of the result 
getMessages ::
  Member TDLib r =>
  -- | Identifier of the chat the messages belong to 
  I53 ->
  -- | Identifiers of the messages to get
  [I53] ->
  Sem r (Error  Messages)
getMessages :: I32 -> [I32] -> Sem r (Error ∪ Messages)
getMessages _1 :: I32
_1 _2 :: [I32]
_2 = GetMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMessages -> Sem r (Error ∪ Messages))
-> GetMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> [I32] -> GetMessages
GetMessages I32
_1 [I32]
_2
-- | Returns information about a file; this is an offline request 
getFile ::
  Member TDLib r =>
  -- | Identifier of the file to get
  I32 ->
  Sem r (Error  File)
getFile :: I32 -> Sem r (Error ∪ File)
getFile _1 :: I32
_1 = GetFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetFile -> Sem r (Error ∪ File))
-> GetFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ I32 -> GetFile
GetFile I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Remote identifier of the file to get 
  T ->
  -- | File type, if known
  FileType ->
  Sem r (Error  File)
getRemoteFile :: T -> FileType -> Sem r (Error ∪ File)
getRemoteFile _1 :: T
_1 _2 :: FileType
_2 = GetRemoteFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRemoteFile -> Sem r (Error ∪ File))
-> GetRemoteFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ T -> FileType -> GetRemoteFile
GetRemoteFile T
_1 FileType
_2
-- | Returns an ordered list of chats in a chat list. Chats are sorted by the pair (chat.position.order, chat.id) in descending 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 ::
  Member TDLib r =>
  -- | The chat list in which to return chats
  ChatList ->
  -- | Chat order to return chats from 
  I64 ->
  -- | Chat identifier to return chats from
  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
  I32 ->
  Sem r (Error  Chats)
getChats :: ChatList -> I64 -> I32 -> I32 -> Sem r (Error ∪ Chats)
getChats _1 :: ChatList
_1 _2 :: I64
_2 _3 :: I32
_3 _4 :: I32
_4 = GetChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChats -> Sem r (Error ∪ Chats))
-> GetChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ ChatList -> I64 -> I32 -> I32 -> GetChats
GetChats ChatList
_1 I64
_2 I32
_3 I32
_4
-- | 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 ::
  Member TDLib r =>
  -- | Username to be resolved
  T ->
  Sem r (Error  Chat)
searchPublicChat :: T -> Sem r (Error ∪ Chat)
searchPublicChat _1 :: T
_1 = SearchPublicChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchPublicChat -> Sem r (Error ∪ Chat))
-> SearchPublicChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ T -> SearchPublicChat
SearchPublicChat T
_1
-- | 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 ::
  Member TDLib r =>
  -- | Query to search for
  T ->
  Sem r (Error  Chats)
searchPublicChats :: T -> Sem r (Error ∪ Chats)
searchPublicChats _1 :: T
_1 = SearchPublicChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchPublicChats -> Sem r (Error ∪ Chats))
-> SearchPublicChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ T -> SearchPublicChats
SearchPublicChats T
_1
-- | 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 main chat list 
searchChats ::
  Member TDLib r =>
  -- | Query to search for. If the query is empty, returns up to 20 recently found chats 
  T ->
  -- | The maximum number of chats to be returned
  I32 ->
  Sem r (Error  Chats)
searchChats :: T -> I32 -> Sem r (Error ∪ Chats)
searchChats _1 :: T
_1 _2 :: I32
_2 = SearchChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChats -> Sem r (Error ∪ Chats))
-> SearchChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SearchChats
SearchChats T
_1 I32
_2
-- | 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 main chat list 
searchChatsOnServer ::
  Member TDLib r =>
  -- | Query to search for 
  T ->
  -- | The maximum number of chats to be returned
  I32 ->
  Sem r (Error  Chats)
searchChatsOnServer :: T -> I32 -> Sem r (Error ∪ Chats)
searchChatsOnServer _1 :: T
_1 _2 :: I32
_2 = SearchChatsOnServer -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChatsOnServer -> Sem r (Error ∪ Chats))
-> SearchChatsOnServer -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SearchChatsOnServer
SearchChatsOnServer T
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Current user location
  Location ->
  Sem r (Error  ChatsNearby)
searchChatsNearby :: Location -> Sem r (Error ∪ ChatsNearby)
searchChatsNearby _1 :: Location
_1 = SearchChatsNearby -> Sem r (Error ∪ ChatsNearby)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChatsNearby -> Sem r (Error ∪ ChatsNearby))
-> SearchChatsNearby -> Sem r (Error ∪ ChatsNearby)
forall a b. (a -> b) -> a -> b
$ Location -> SearchChatsNearby
SearchChatsNearby Location
_1
-- | Returns a list of frequently used chats. Supported only if the chat info database is enabled 
getTopChats ::
  Member TDLib r =>
  -- | Category of chats to be returned 
  TopChatCategory ->
  -- | The maximum number of chats to be returned; up to 30
  I32 ->
  Sem r (Error  Chats)
getTopChats :: TopChatCategory -> I32 -> Sem r (Error ∪ Chats)
getTopChats _1 :: TopChatCategory
_1 _2 :: I32
_2 = GetTopChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetTopChats -> Sem r (Error ∪ Chats))
-> GetTopChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ TopChatCategory -> I32 -> GetTopChats
GetTopChats TopChatCategory
_1 I32
_2
-- | Removes a chat from the list of frequently used chats. Supported only if the chat info database is enabled 
removeTopChat ::
  Member TDLib r =>
  -- | Category of frequently used chats 
  TopChatCategory ->
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
removeTopChat :: TopChatCategory -> I32 -> Sem r (Error ∪ Ok)
removeTopChat _1 :: TopChatCategory
_1 _2 :: I32
_2 = RemoveTopChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveTopChat -> Sem r (Error ∪ Ok))
-> RemoveTopChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TopChatCategory -> I32 -> RemoveTopChat
RemoveTopChat TopChatCategory
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to add
  I53 ->
  Sem r (Error  Ok)
addRecentlyFoundChat :: I32 -> Sem r (Error ∪ Ok)
addRecentlyFoundChat _1 :: I32
_1 = AddRecentlyFoundChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddRecentlyFoundChat -> Sem r (Error ∪ Ok))
-> AddRecentlyFoundChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> AddRecentlyFoundChat
AddRecentlyFoundChat I32
_1
-- | Removes a chat from the list of recently found chats 
removeRecentlyFoundChat ::
  Member TDLib r =>
  -- | Identifier of the chat to be removed
  I53 ->
  Sem r (Error  Ok)
removeRecentlyFoundChat :: I32 -> Sem r (Error ∪ Ok)
removeRecentlyFoundChat _1 :: I32
_1 = RemoveRecentlyFoundChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveRecentlyFoundChat -> Sem r (Error ∪ Ok))
-> RemoveRecentlyFoundChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> RemoveRecentlyFoundChat
RemoveRecentlyFoundChat I32
_1
-- | Clears the list of recently found chats
clearRecentlyFoundChats ::
  Member TDLib r =>
  Sem r (Error  Ok)
clearRecentlyFoundChats :: Sem r (Error ∪ Ok)
clearRecentlyFoundChats  = ClearRecentlyFoundChats -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ClearRecentlyFoundChats -> Sem r (Error ∪ Ok))
-> ClearRecentlyFoundChats -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ClearRecentlyFoundChats
ClearRecentlyFoundChats 
-- | Checks whether a username can be set for a chat 
checkChatUsername ::
  Member TDLib r =>
  -- | 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 
  I53 ->
  -- | Username to be checked
  T ->
  Sem r (Error  CheckChatUsernameResult)
checkChatUsername :: I32 -> T -> Sem r (Error ∪ CheckChatUsernameResult)
checkChatUsername _1 :: I32
_1 _2 :: T
_2 = CheckChatUsername -> Sem r (Error ∪ CheckChatUsernameResult)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckChatUsername -> Sem r (Error ∪ CheckChatUsernameResult))
-> CheckChatUsername -> Sem r (Error ∪ CheckChatUsernameResult)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> CheckChatUsername
CheckChatUsername I32
_1 T
_2
-- | Returns a list of public chats of the specified type, owned by the user 
getCreatedPublicChats ::
  Member TDLib r =>
  -- | Type of the public chats to return
  PublicChatType ->
  Sem r (Error  Chats)
getCreatedPublicChats :: PublicChatType -> Sem r (Error ∪ Chats)
getCreatedPublicChats _1 :: PublicChatType
_1 = GetCreatedPublicChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetCreatedPublicChats -> Sem r (Error ∪ Chats))
-> GetCreatedPublicChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ PublicChatType -> GetCreatedPublicChats
GetCreatedPublicChats PublicChatType
_1
-- | Checks whether the maximum number of owned public chats has been reached. Returns corresponding error if the limit was reached 
checkCreatedPublicChatsLimit ::
  Member TDLib r =>
  -- | Type of the public chats, for which to check the limit
  PublicChatType ->
  Sem r (Error  Ok)
checkCreatedPublicChatsLimit :: PublicChatType -> Sem r (Error ∪ Ok)
checkCreatedPublicChatsLimit _1 :: PublicChatType
_1 = CheckCreatedPublicChatsLimit -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckCreatedPublicChatsLimit -> Sem r (Error ∪ Ok))
-> CheckCreatedPublicChatsLimit -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ PublicChatType -> CheckCreatedPublicChatsLimit
CheckCreatedPublicChatsLimit PublicChatType
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Chats)
getSuitableDiscussionChats :: Sem r (Error ∪ Chats)
getSuitableDiscussionChats  = GetSuitableDiscussionChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSuitableDiscussionChats -> Sem r (Error ∪ Chats))
-> GetSuitableDiscussionChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ GetSuitableDiscussionChats
GetSuitableDiscussionChats 
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Chats)
getInactiveSupergroupChats :: Sem r (Error ∪ Chats)
getInactiveSupergroupChats  = GetInactiveSupergroupChats -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetInactiveSupergroupChats -> Sem r (Error ∪ Chats))
-> GetInactiveSupergroupChats -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ GetInactiveSupergroupChats
GetInactiveSupergroupChats 
-- | Returns a list of common group chats with a given user. Chats are sorted by their type and creation date 
getGroupsInCommon ::
  Member TDLib r =>
  -- | User identifier 
  I32 ->
  -- | Chat identifier starting from which to return chats; use 0 for the first request 
  I53 ->
  -- | The maximum number of chats to be returned; up to 100
  I32 ->
  Sem r (Error  Chats)
getGroupsInCommon :: I32 -> I32 -> I32 -> Sem r (Error ∪ Chats)
getGroupsInCommon _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = GetGroupsInCommon -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetGroupsInCommon -> Sem r (Error ∪ Chats))
-> GetGroupsInCommon -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> GetGroupsInCommon
GetGroupsInCommon I32
_1 I32
_2 I32
_3
-- | Returns messages in a chat. The messages are returned in a reverse chronological order (i.e., in order of decreasing message_id).
getChatHistory ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  -- | Identifier of the message starting from which history must be fetched; use 0 to get results from the last message
  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
  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
  I32 ->
  -- | If true, returns only messages that are available locally without sending network requests
  Bool ->
  Sem r (Error  Messages)
getChatHistory :: I32 -> I32 -> I32 -> I32 -> Bool -> Sem r (Error ∪ Messages)
getChatHistory _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: Bool
_5 = GetChatHistory -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatHistory -> Sem r (Error ∪ Messages))
-> GetChatHistory -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> I32 -> Bool -> GetChatHistory
GetChatHistory I32
_1 I32
_2 I32
_3 I32
_4 Bool
_5
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Pass true if the chat should be removed from the chat list 
  Bool ->
  -- | Pass true to try to delete chat history for all users
  Bool ->
  Sem r (Error  Ok)
deleteChatHistory :: I32 -> Bool -> Bool -> Sem r (Error ∪ Ok)
deleteChatHistory _1 :: I32
_1 _2 :: Bool
_2 _3 :: Bool
_3 = DeleteChatHistory -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteChatHistory -> Sem r (Error ∪ Ok))
-> DeleteChatHistory -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> Bool -> DeleteChatHistory
DeleteChatHistory I32
_1 Bool
_2 Bool
_3
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat in which to search messages
  I53 ->
  -- | Query to search for
  T ->
  -- | If not 0, only messages sent by the specified user will be returned. Not supported in secret chats
  I32 ->
  -- | Identifier of the message starting from which history must be fetched; use 0 to get results from the last message
  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
  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
  I32 ->
  -- | Filter for message content in the search results
  SearchMessagesFilter ->
  Sem r (Error  Messages)
searchChatMessages :: I32
-> T
-> I32
-> I32
-> I32
-> I32
-> SearchMessagesFilter
-> Sem r (Error ∪ Messages)
searchChatMessages _1 :: I32
_1 _2 :: T
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: I32
_5 _6 :: I32
_6 _7 :: SearchMessagesFilter
_7 = SearchChatMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChatMessages -> Sem r (Error ∪ Messages))
-> SearchChatMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32
-> T
-> I32
-> I32
-> I32
-> I32
-> SearchMessagesFilter
-> SearchChatMessages
SearchChatMessages I32
_1 T
_2 I32
_3 I32
_4 I32
_5 I32
_6 SearchMessagesFilter
_7
-- | 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 ::
  Member TDLib r =>
  -- | Chat list in which to search messages; pass null to search in all chats regardless of their chat list
  ChatList ->
  -- | Query to search for
  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
  I32 ->
  -- | The chat identifier of the last found message, or 0 for the first request
  I53 ->
  -- | The message identifier of the last found message, or 0 for the first request
  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
  I32 ->
  Sem r (Error  Messages)
searchMessages :: ChatList
-> T -> I32 -> I32 -> I32 -> I32 -> Sem r (Error ∪ Messages)
searchMessages _1 :: ChatList
_1 _2 :: T
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: I32
_5 _6 :: I32
_6 = SearchMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchMessages -> Sem r (Error ∪ Messages))
-> SearchMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ ChatList -> T -> I32 -> I32 -> I32 -> I32 -> SearchMessages
SearchMessages ChatList
_1 T
_2 I32
_3 I32
_4 I32
_5 I32
_6
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat in which to search. Specify 0 to search in all secret chats 
  I53 ->
  -- | Query to search for. If empty, searchChatMessages should be used instead
  T ->
  -- | The identifier from the result of a previous request, use 0 to get results from the last message
  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
  I32 ->
  -- | A filter for the content of messages in the search results
  SearchMessagesFilter ->
  Sem r (Error  FoundMessages)
searchSecretMessages :: I32
-> T
-> I64
-> I32
-> SearchMessagesFilter
-> Sem r (Error ∪ FoundMessages)
searchSecretMessages _1 :: I32
_1 _2 :: T
_2 _3 :: I64
_3 _4 :: I32
_4 _5 :: SearchMessagesFilter
_5 = SearchSecretMessages -> Sem r (Error ∪ FoundMessages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchSecretMessages -> Sem r (Error ∪ FoundMessages))
-> SearchSecretMessages -> Sem r (Error ∪ FoundMessages)
forall a b. (a -> b) -> a -> b
$ I32
-> T -> I64 -> I32 -> SearchMessagesFilter -> SearchSecretMessages
SearchSecretMessages I32
_1 T
_2 I64
_3 I32
_4 SearchMessagesFilter
_5
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the message from which to search; use 0 to get results from the last message
  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 
  I32 ->
  -- | If true, returns only messages with missed calls
  Bool ->
  Sem r (Error  Messages)
searchCallMessages :: I32 -> I32 -> Bool -> Sem r (Error ∪ Messages)
searchCallMessages _1 :: I32
_1 _2 :: I32
_2 _3 :: Bool
_3 = SearchCallMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchCallMessages -> Sem r (Error ∪ Messages))
-> SearchCallMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> Bool -> SearchCallMessages
SearchCallMessages I32
_1 I32
_2 Bool
_3
-- | Returns information about the recent locations of chat members that were sent to the chat. Returns up to 1 location message per user 
searchChatRecentLocationMessages ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The maximum number of messages to be returned
  I32 ->
  Sem r (Error  Messages)
searchChatRecentLocationMessages :: I32 -> I32 -> Sem r (Error ∪ Messages)
searchChatRecentLocationMessages _1 :: I32
_1 _2 :: I32
_2 = SearchChatRecentLocationMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChatRecentLocationMessages -> Sem r (Error ∪ Messages))
-> SearchChatRecentLocationMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> SearchChatRecentLocationMessages
SearchChatRecentLocationMessages I32
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Messages)
getActiveLiveLocationMessages :: Sem r (Error ∪ Messages)
getActiveLiveLocationMessages  = GetActiveLiveLocationMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetActiveLiveLocationMessages -> Sem r (Error ∪ Messages))
-> GetActiveLiveLocationMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ GetActiveLiveLocationMessages
GetActiveLiveLocationMessages 
-- | Returns the last message sent in a chat no later than the specified date 
getChatMessageByDate ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Point in time (Unix timestamp) relative to which to search for messages
  I32 ->
  Sem r (Error  Message)
getChatMessageByDate :: I32 -> I32 -> Sem r (Error ∪ Message)
getChatMessageByDate _1 :: I32
_1 _2 :: I32
_2 = GetChatMessageByDate -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatMessageByDate -> Sem r (Error ∪ Message))
-> GetChatMessageByDate -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetChatMessageByDate
GetChatMessageByDate I32
_1 I32
_2
-- | Returns approximate number of messages of the specified type in the chat 
getChatMessageCount ::
  Member TDLib r =>
  -- | Identifier of the chat in which to count messages 
  I53 ->
  -- | Filter for message content; searchMessagesFilterEmpty is unsupported in this function 
  SearchMessagesFilter ->
  -- | If true, returns count that is available locally without sending network requests, returning -1 if the number of messages is unknown
  Bool ->
  Sem r (Error  Count)
getChatMessageCount :: I32 -> SearchMessagesFilter -> Bool -> Sem r (Error ∪ Count)
getChatMessageCount _1 :: I32
_1 _2 :: SearchMessagesFilter
_2 _3 :: Bool
_3 = GetChatMessageCount -> Sem r (Error ∪ Count)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatMessageCount -> Sem r (Error ∪ Count))
-> GetChatMessageCount -> Sem r (Error ∪ Count)
forall a b. (a -> b) -> a -> b
$ I32 -> SearchMessagesFilter -> Bool -> GetChatMessageCount
GetChatMessageCount I32
_1 SearchMessagesFilter
_2 Bool
_3
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Messages)
getChatScheduledMessages :: I32 -> Sem r (Error ∪ Messages)
getChatScheduledMessages _1 :: I32
_1 = GetChatScheduledMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatScheduledMessages -> Sem r (Error ∪ Messages))
-> GetChatScheduledMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChatScheduledMessages
GetChatScheduledMessages I32
_1
-- | Removes an active notification from notification list. Needs to be called only if the notification is removed by the current user 
removeNotification ::
  Member TDLib r =>
  -- | Identifier of notification group to which the notification belongs 
  I32 ->
  -- | Identifier of removed notification
  I32 ->
  Sem r (Error  Ok)
removeNotification :: I32 -> I32 -> Sem r (Error ∪ Ok)
removeNotification _1 :: I32
_1 _2 :: I32
_2 = RemoveNotification -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveNotification -> Sem r (Error ∪ Ok))
-> RemoveNotification -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> RemoveNotification
RemoveNotification I32
_1 I32
_2
-- | Removes a group of active notifications. Needs to be called only if the notification group is removed by the current user 
removeNotificationGroup ::
  Member TDLib r =>
  -- | Notification group identifier 
  I32 ->
  -- | The maximum identifier of removed notifications
  I32 ->
  Sem r (Error  Ok)
removeNotificationGroup :: I32 -> I32 -> Sem r (Error ∪ Ok)
removeNotificationGroup _1 :: I32
_1 _2 :: I32
_2 = RemoveNotificationGroup -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveNotificationGroup -> Sem r (Error ∪ Ok))
-> RemoveNotificationGroup -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> RemoveNotificationGroup
RemoveNotificationGroup I32
_1 I32
_2
-- | Returns a public HTTPS link to a message. Available only for messages in supergroups and channels with a username
getPublicMessageLink ::
  Member TDLib r =>
  -- | Identifier of the chat to which the message belongs
  I53 ->
  -- | Identifier of the message
  I53 ->
  -- | Pass true if a link for a whole media album should be returned
  Bool ->
  Sem r (Error  PublicMessageLink)
getPublicMessageLink :: I32 -> I32 -> Bool -> Sem r (Error ∪ PublicMessageLink)
getPublicMessageLink _1 :: I32
_1 _2 :: I32
_2 _3 :: Bool
_3 = GetPublicMessageLink -> Sem r (Error ∪ PublicMessageLink)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPublicMessageLink -> Sem r (Error ∪ PublicMessageLink))
-> GetPublicMessageLink -> Sem r (Error ∪ PublicMessageLink)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> Bool -> GetPublicMessageLink
GetPublicMessageLink I32
_1 I32
_2 Bool
_3
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to which the message belongs
  I53 ->
  -- | Identifier of the message
  I53 ->
  Sem r (Error  HttpUrl)
getMessageLink :: I32 -> I32 -> Sem r (Error ∪ HttpUrl)
getMessageLink _1 :: I32
_1 _2 :: I32
_2 = GetMessageLink -> Sem r (Error ∪ HttpUrl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMessageLink -> Sem r (Error ∪ HttpUrl))
-> GetMessageLink -> Sem r (Error ∪ HttpUrl)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetMessageLink
GetMessageLink I32
_1 I32
_2
-- | Returns information about a public or private message link 
getMessageLinkInfo ::
  Member TDLib r =>
  -- | The message link in the format "https://t.me/c/...", or "tg://privatepost?...", or "https://t.me/username/...", or "tg://resolve?..."
  T ->
  Sem r (Error  MessageLinkInfo)
getMessageLinkInfo :: T -> Sem r (Error ∪ MessageLinkInfo)
getMessageLinkInfo _1 :: T
_1 = GetMessageLinkInfo -> Sem r (Error ∪ MessageLinkInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMessageLinkInfo -> Sem r (Error ∪ MessageLinkInfo))
-> GetMessageLinkInfo -> Sem r (Error ∪ MessageLinkInfo)
forall a b. (a -> b) -> a -> b
$ T -> GetMessageLinkInfo
GetMessageLinkInfo T
_1
-- | Sends a message. Returns the sent message
sendMessage ::
  Member TDLib r =>
  -- | Target chat 
  I53 ->
  -- | Identifier of the message to reply to or 0
  I53 ->
  -- | Options to be used to send the message
  SendMessageOptions ->
  -- | Markup for replying to the message; for bots only 
  ReplyMarkup ->
  -- | The content of the message to be sent
  InputMessageContent ->
  Sem r (Error  Message)
sendMessage :: I32
-> I32
-> SendMessageOptions
-> ReplyMarkup
-> InputMessageContent
-> Sem r (Error ∪ Message)
sendMessage _1 :: I32
_1 _2 :: I32
_2 _3 :: SendMessageOptions
_3 _4 :: ReplyMarkup
_4 _5 :: InputMessageContent
_5 = SendMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendMessage -> Sem r (Error ∪ Message))
-> SendMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32
-> I32
-> SendMessageOptions
-> ReplyMarkup
-> InputMessageContent
-> SendMessage
SendMessage I32
_1 I32
_2 SendMessageOptions
_3 ReplyMarkup
_4 InputMessageContent
_5
-- | Sends messages grouped together into an album. Currently only photo and video messages can be grouped into an album. Returns sent messages
sendMessageAlbum ::
  Member TDLib r =>
  -- | Target chat 
  I53 ->
  -- | Identifier of a message to reply to or 0
  I53 ->
  -- | Options to be used to send the messages
  SendMessageOptions ->
  -- | Contents of messages to be sent
  [InputMessageContent] ->
  Sem r (Error  Messages)
sendMessageAlbum :: I32
-> I32
-> SendMessageOptions
-> [InputMessageContent]
-> Sem r (Error ∪ Messages)
sendMessageAlbum _1 :: I32
_1 _2 :: I32
_2 _3 :: SendMessageOptions
_3 _4 :: [InputMessageContent]
_4 = SendMessageAlbum -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendMessageAlbum -> Sem r (Error ∪ Messages))
-> SendMessageAlbum -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32
-> I32
-> SendMessageOptions
-> [InputMessageContent]
-> SendMessageAlbum
SendMessageAlbum I32
_1 I32
_2 SendMessageOptions
_3 [InputMessageContent]
_4
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the bot 
  I32 ->
  -- | Identifier of the target chat 
  I53 ->
  -- | A hidden parameter sent to the bot for deep linking purposes (https://core.telegram.org/bots#deep-linking)
  T ->
  Sem r (Error  Message)
sendBotStartMessage :: I32 -> I32 -> T -> Sem r (Error ∪ Message)
sendBotStartMessage _1 :: I32
_1 _2 :: I32
_2 _3 :: T
_3 = SendBotStartMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendBotStartMessage -> Sem r (Error ∪ Message))
-> SendBotStartMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> T -> SendBotStartMessage
SendBotStartMessage I32
_1 I32
_2 T
_3
-- | Sends the result of an inline query as a message. Returns the sent message. Always clears a chat draft message
sendInlineQueryResultMessage ::
  Member TDLib r =>
  -- | Target chat 
  I53 ->
  -- | Identifier of a message to reply to or 0
  I53 ->
  -- | Options to be used to send the message
  SendMessageOptions ->
  -- | Identifier of the inline query 
  I64 ->
  -- | Identifier of the inline result
  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")
  Bool ->
  Sem r (Error  Message)
sendInlineQueryResultMessage :: I32
-> I32
-> SendMessageOptions
-> I64
-> T
-> Bool
-> Sem r (Error ∪ Message)
sendInlineQueryResultMessage _1 :: I32
_1 _2 :: I32
_2 _3 :: SendMessageOptions
_3 _4 :: I64
_4 _5 :: T
_5 _6 :: Bool
_6 = SendInlineQueryResultMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendInlineQueryResultMessage -> Sem r (Error ∪ Message))
-> SendInlineQueryResultMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32
-> I32
-> SendMessageOptions
-> I64
-> T
-> Bool
-> SendInlineQueryResultMessage
SendInlineQueryResultMessage I32
_1 I32
_2 SendMessageOptions
_3 I64
_4 T
_5 Bool
_6
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to which to forward messages 
  I53 ->
  -- | Identifier of the chat from which to forward messages 
  I53 ->
  -- | Identifiers of the messages to forward
  [I53] ->
  -- | Options to be used to send the messages
  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
  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
  Bool ->
  -- | True, if media captions of message copies needs to be removed. Ignored if send_copy is false
  Bool ->
  Sem r (Error  Messages)
forwardMessages :: I32
-> I32
-> [I32]
-> SendMessageOptions
-> Bool
-> Bool
-> Bool
-> Sem r (Error ∪ Messages)
forwardMessages _1 :: I32
_1 _2 :: I32
_2 _3 :: [I32]
_3 _4 :: SendMessageOptions
_4 _5 :: Bool
_5 _6 :: Bool
_6 _7 :: Bool
_7 = ForwardMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ForwardMessages -> Sem r (Error ∪ Messages))
-> ForwardMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32
-> I32
-> [I32]
-> SendMessageOptions
-> Bool
-> Bool
-> Bool
-> ForwardMessages
ForwardMessages I32
_1 I32
_2 [I32]
_3 SendMessageOptions
_4 Bool
_5 Bool
_6 Bool
_7
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to send messages 
  I53 ->
  -- | Identifiers of the messages to resend. Message identifiers must be in a strictly increasing order
  [I53] ->
  Sem r (Error  Messages)
resendMessages :: I32 -> [I32] -> Sem r (Error ∪ Messages)
resendMessages _1 :: I32
_1 _2 :: [I32]
_2 = ResendMessages -> Sem r (Error ∪ Messages)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendMessages -> Sem r (Error ∪ Messages))
-> ResendMessages -> Sem r (Error ∪ Messages)
forall a b. (a -> b) -> a -> b
$ I32 -> [I32] -> ResendMessages
ResendMessages I32
_1 [I32]
_2
-- | Changes the current TTL setting (sets a new self-destruct timer) in a secret chat and sends the corresponding message 
sendChatSetTtlMessage ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New TTL value, in seconds
  I32 ->
  Sem r (Error  Message)
sendChatSetTtlMessage :: I32 -> I32 -> Sem r (Error ∪ Message)
sendChatSetTtlMessage _1 :: I32
_1 _2 :: I32
_2 = SendChatSetTtlMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendChatSetTtlMessage -> Sem r (Error ∪ Message))
-> SendChatSetTtlMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> SendChatSetTtlMessage
SendChatSetTtlMessage I32
_1 I32
_2
-- | Sends a notification about a screenshot taken in a chat. Supported only in private and secret chats 
sendChatScreenshotTakenNotification ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
sendChatScreenshotTakenNotification :: I32 -> Sem r (Error ∪ Ok)
sendChatScreenshotTakenNotification _1 :: I32
_1 = SendChatScreenshotTakenNotification -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendChatScreenshotTakenNotification -> Sem r (Error ∪ Ok))
-> SendChatScreenshotTakenNotification -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> SendChatScreenshotTakenNotification
SendChatScreenshotTakenNotification I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Target chat 
  I53 ->
  -- | Identifier of the user who will be shown as the sender of the message; may be 0 for channel posts
  I32 ->
  -- | Identifier of the message to reply to or 0 
  I53 ->
  -- | Pass true to disable notification for the message 
  Bool ->
  -- | The content of the message to be added
  InputMessageContent ->
  Sem r (Error  Message)
addLocalMessage :: I32
-> I32
-> I32
-> Bool
-> InputMessageContent
-> Sem r (Error ∪ Message)
addLocalMessage _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: Bool
_4 _5 :: InputMessageContent
_5 = AddLocalMessage -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddLocalMessage -> Sem r (Error ∪ Message))
-> AddLocalMessage -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> Bool -> InputMessageContent -> AddLocalMessage
AddLocalMessage I32
_1 I32
_2 I32
_3 Bool
_4 InputMessageContent
_5
-- | Deletes messages 
deleteMessages ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Identifiers of the messages to be deleted 
  [I53] ->
  -- | Pass true to try to delete messages for all chat members. Always true for supergroups, channels and secret chats
  Bool ->
  Sem r (Error  Ok)
deleteMessages :: I32 -> [I32] -> Bool -> Sem r (Error ∪ Ok)
deleteMessages _1 :: I32
_1 _2 :: [I32]
_2 _3 :: Bool
_3 = DeleteMessages -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteMessages -> Sem r (Error ∪ Ok))
-> DeleteMessages -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> [I32] -> Bool -> DeleteMessages
DeleteMessages I32
_1 [I32]
_2 Bool
_3
-- | Deletes all messages sent by the specified user to a chat. Supported only for supergroups; requires can_delete_messages administrator privileges 
deleteChatMessagesFromUser ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | User identifier
  I32 ->
  Sem r (Error  Ok)
deleteChatMessagesFromUser :: I32 -> I32 -> Sem r (Error ∪ Ok)
deleteChatMessagesFromUser _1 :: I32
_1 _2 :: I32
_2 = DeleteChatMessagesFromUser -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteChatMessagesFromUser -> Sem r (Error ∪ Ok))
-> DeleteChatMessagesFromUser -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> DeleteChatMessagesFromUser
DeleteChatMessagesFromUser I32
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message reply markup; for bots only 
  ReplyMarkup ->
  -- | New text content of the message. Should be of type InputMessageText
  InputMessageContent ->
  Sem r (Error  Message)
editMessageText :: I32
-> I32
-> ReplyMarkup
-> InputMessageContent
-> Sem r (Error ∪ Message)
editMessageText _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 _4 :: InputMessageContent
_4 = EditMessageText -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageText -> Sem r (Error ∪ Message))
-> EditMessageText -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> ReplyMarkup -> InputMessageContent -> EditMessageText
EditMessageText I32
_1 I32
_2 ReplyMarkup
_3 InputMessageContent
_4
-- | 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 ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message reply markup; for bots only 
  ReplyMarkup ->
  -- | New location content of the message; may be null. Pass null to stop sharing the live location
  (Maybe) (Location) ->
  Sem r (Error  Message)
editMessageLiveLocation :: I32
-> I32 -> ReplyMarkup -> Maybe Location -> Sem r (Error ∪ Message)
editMessageLiveLocation _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 _4 :: Maybe Location
_4 = EditMessageLiveLocation -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageLiveLocation -> Sem r (Error ∪ Message))
-> EditMessageLiveLocation -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32
-> I32 -> ReplyMarkup -> Maybe Location -> EditMessageLiveLocation
EditMessageLiveLocation I32
_1 I32
_2 ReplyMarkup
_3 Maybe Location
_4
-- | 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 ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message reply markup; for bots only 
  ReplyMarkup ->
  -- | New content of the message. Must be one of the following types: InputMessageAnimation, InputMessageAudio, InputMessageDocument, InputMessagePhoto or InputMessageVideo
  InputMessageContent ->
  Sem r (Error  Message)
editMessageMedia :: I32
-> I32
-> ReplyMarkup
-> InputMessageContent
-> Sem r (Error ∪ Message)
editMessageMedia _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 _4 :: InputMessageContent
_4 = EditMessageMedia -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageMedia -> Sem r (Error ∪ Message))
-> EditMessageMedia -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32
-> I32 -> ReplyMarkup -> InputMessageContent -> EditMessageMedia
EditMessageMedia I32
_1 I32
_2 ReplyMarkup
_3 InputMessageContent
_4
-- | Edits the message content caption. Returns the edited message after the edit is completed on the server side
editMessageCaption ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message reply markup; for bots only 
  ReplyMarkup ->
  -- | New message content caption; 0-GetOption("message_caption_length_max") characters
  FormattedText ->
  Sem r (Error  Message)
editMessageCaption :: I32
-> I32 -> ReplyMarkup -> FormattedText -> Sem r (Error ∪ Message)
editMessageCaption _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 _4 :: FormattedText
_4 = EditMessageCaption -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageCaption -> Sem r (Error ∪ Message))
-> EditMessageCaption -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> ReplyMarkup -> FormattedText -> EditMessageCaption
EditMessageCaption I32
_1 I32
_2 ReplyMarkup
_3 FormattedText
_4
-- | Edits the message reply markup; for bots only. Returns the edited message after the edit is completed on the server side
editMessageReplyMarkup ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message reply markup
  ReplyMarkup ->
  Sem r (Error  Message)
editMessageReplyMarkup :: I32 -> I32 -> ReplyMarkup -> Sem r (Error ∪ Message)
editMessageReplyMarkup _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 = EditMessageReplyMarkup -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageReplyMarkup -> Sem r (Error ∪ Message))
-> EditMessageReplyMarkup -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> ReplyMarkup -> EditMessageReplyMarkup
EditMessageReplyMarkup I32
_1 I32
_2 ReplyMarkup
_3
-- | Edits the text of an inline text or game message sent via a bot; for bots only 
editInlineMessageText ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | The new message reply markup 
  ReplyMarkup ->
  -- | New text content of the message. Should be of type InputMessageText
  InputMessageContent ->
  Sem r (Error  Ok)
editInlineMessageText :: T -> ReplyMarkup -> InputMessageContent -> Sem r (Error ∪ Ok)
editInlineMessageText _1 :: T
_1 _2 :: ReplyMarkup
_2 _3 :: InputMessageContent
_3 = EditInlineMessageText -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditInlineMessageText -> Sem r (Error ∪ Ok))
-> EditInlineMessageText -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ReplyMarkup -> InputMessageContent -> EditInlineMessageText
EditInlineMessageText T
_1 ReplyMarkup
_2 InputMessageContent
_3
-- | Edits the content of a live location in an inline message sent via a bot; for bots only 
editInlineMessageLiveLocation ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | The new message reply markup 
  ReplyMarkup ->
  -- | New location content of the message; may be null. Pass null to stop sharing the live location
  (Maybe) (Location) ->
  Sem r (Error  Ok)
editInlineMessageLiveLocation :: T -> ReplyMarkup -> Maybe Location -> Sem r (Error ∪ Ok)
editInlineMessageLiveLocation _1 :: T
_1 _2 :: ReplyMarkup
_2 _3 :: Maybe Location
_3 = EditInlineMessageLiveLocation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditInlineMessageLiveLocation -> Sem r (Error ∪ Ok))
-> EditInlineMessageLiveLocation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ReplyMarkup -> Maybe Location -> EditInlineMessageLiveLocation
EditInlineMessageLiveLocation T
_1 ReplyMarkup
_2 Maybe Location
_3
-- | 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 ::
  Member TDLib r =>
  -- | Inline message identifier
  T ->
  -- | The new message reply markup; for bots only 
  ReplyMarkup ->
  -- | New content of the message. Must be one of the following types: InputMessageAnimation, InputMessageAudio, InputMessageDocument, InputMessagePhoto or InputMessageVideo
  InputMessageContent ->
  Sem r (Error  Ok)
editInlineMessageMedia :: T -> ReplyMarkup -> InputMessageContent -> Sem r (Error ∪ Ok)
editInlineMessageMedia _1 :: T
_1 _2 :: ReplyMarkup
_2 _3 :: InputMessageContent
_3 = EditInlineMessageMedia -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditInlineMessageMedia -> Sem r (Error ∪ Ok))
-> EditInlineMessageMedia -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ReplyMarkup -> InputMessageContent -> EditInlineMessageMedia
EditInlineMessageMedia T
_1 ReplyMarkup
_2 InputMessageContent
_3
-- | Edits the caption of an inline message sent via a bot; for bots only 
editInlineMessageCaption ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | The new message reply markup 
  ReplyMarkup ->
  -- | New message content caption; 0-GetOption("message_caption_length_max") characters
  FormattedText ->
  Sem r (Error  Ok)
editInlineMessageCaption :: T -> ReplyMarkup -> FormattedText -> Sem r (Error ∪ Ok)
editInlineMessageCaption _1 :: T
_1 _2 :: ReplyMarkup
_2 _3 :: FormattedText
_3 = EditInlineMessageCaption -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditInlineMessageCaption -> Sem r (Error ∪ Ok))
-> EditInlineMessageCaption -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ReplyMarkup -> FormattedText -> EditInlineMessageCaption
EditInlineMessageCaption T
_1 ReplyMarkup
_2 FormattedText
_3
-- | Edits the reply markup of an inline message sent via a bot; for bots only 
editInlineMessageReplyMarkup ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | The new message reply markup
  ReplyMarkup ->
  Sem r (Error  Ok)
editInlineMessageReplyMarkup :: T -> ReplyMarkup -> Sem r (Error ∪ Ok)
editInlineMessageReplyMarkup _1 :: T
_1 _2 :: ReplyMarkup
_2 = EditInlineMessageReplyMarkup -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditInlineMessageReplyMarkup -> Sem r (Error ∪ Ok))
-> EditInlineMessageReplyMarkup -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ReplyMarkup -> EditInlineMessageReplyMarkup
EditInlineMessageReplyMarkup T
_1 ReplyMarkup
_2
-- | 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 ::
  Member TDLib r =>
  -- | The chat the message belongs to 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | The new message scheduling state. Pass null to send the message immediately
  MessageSchedulingState ->
  Sem r (Error  Ok)
editMessageSchedulingState :: I32 -> I32 -> MessageSchedulingState -> Sem r (Error ∪ Ok)
editMessageSchedulingState _1 :: I32
_1 _2 :: I32
_2 _3 :: MessageSchedulingState
_3 = EditMessageSchedulingState -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditMessageSchedulingState -> Sem r (Error ∪ Ok))
-> EditMessageSchedulingState -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> MessageSchedulingState -> EditMessageSchedulingState
EditMessageSchedulingState I32
_1 I32
_2 MessageSchedulingState
_3
-- | 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 ::
  Member TDLib r =>
  -- | The text in which to look for entites
  T ->
  Sem r (Error  TextEntities)
getTextEntities :: T -> Sem r (Error ∪ TextEntities)
getTextEntities _1 :: T
_1 = GetTextEntities -> Sem r (Error ∪ TextEntities)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetTextEntities -> Sem r (Error ∪ TextEntities))
-> GetTextEntities -> Sem r (Error ∪ TextEntities)
forall a b. (a -> b) -> a -> b
$ T -> GetTextEntities
GetTextEntities T
_1
-- | 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 ::
  Member TDLib r =>
  -- | The text to parse 
  T ->
  -- | Text parse mode
  TextParseMode ->
  Sem r (Error  FormattedText)
parseTextEntities :: T -> TextParseMode -> Sem r (Error ∪ FormattedText)
parseTextEntities _1 :: T
_1 _2 :: TextParseMode
_2 = ParseTextEntities -> Sem r (Error ∪ FormattedText)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ParseTextEntities -> Sem r (Error ∪ FormattedText))
-> ParseTextEntities -> Sem r (Error ∪ FormattedText)
forall a b. (a -> b) -> a -> b
$ T -> TextParseMode -> ParseTextEntities
ParseTextEntities T
_1 TextParseMode
_2
-- | 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 ::
  Member TDLib r =>
  -- | The text to parse. For example, "__italic__ ~~strikethrough~~ **bold** `code` ```pre``` __[italic__ text_url](telegram.org) __italic**bold italic__bold**"
  FormattedText ->
  Sem r (Error  FormattedText)
parseMarkdown :: FormattedText -> Sem r (Error ∪ FormattedText)
parseMarkdown _1 :: FormattedText
_1 = ParseMarkdown -> Sem r (Error ∪ FormattedText)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ParseMarkdown -> Sem r (Error ∪ FormattedText))
-> ParseMarkdown -> Sem r (Error ∪ FormattedText)
forall a b. (a -> b) -> a -> b
$ FormattedText -> ParseMarkdown
ParseMarkdown FormattedText
_1
-- | 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 ::
  Member TDLib r =>
  -- | The text
  FormattedText ->
  Sem r (Error  FormattedText)
getMarkdownText :: FormattedText -> Sem r (Error ∪ FormattedText)
getMarkdownText _1 :: FormattedText
_1 = GetMarkdownText -> Sem r (Error ∪ FormattedText)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMarkdownText -> Sem r (Error ∪ FormattedText))
-> GetMarkdownText -> Sem r (Error ∪ FormattedText)
forall a b. (a -> b) -> a -> b
$ FormattedText -> GetMarkdownText
GetMarkdownText FormattedText
_1
-- | 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 ::
  Member TDLib r =>
  -- | The name of the file or path to the file
  T ->
  Sem r (Error  Text)
getFileMimeType :: T -> Sem r (Error ∪ Text)
getFileMimeType _1 :: T
_1 = GetFileMimeType -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetFileMimeType -> Sem r (Error ∪ Text))
-> GetFileMimeType -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ T -> GetFileMimeType
GetFileMimeType T
_1
-- | 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 ::
  Member TDLib r =>
  -- | The MIME type of the file
  T ->
  Sem r (Error  Text)
getFileExtension :: T -> Sem r (Error ∪ Text)
getFileExtension _1 :: T
_1 = GetFileExtension -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetFileExtension -> Sem r (Error ∪ Text))
-> GetFileExtension -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ T -> GetFileExtension
GetFileExtension T
_1
-- | 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 ::
  Member TDLib r =>
  -- | File name or path to the file
  T ->
  Sem r (Error  Text)
cleanFileName :: T -> Sem r (Error ∪ Text)
cleanFileName _1 :: T
_1 = CleanFileName -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CleanFileName -> Sem r (Error ∪ Text))
-> CleanFileName -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ T -> CleanFileName
CleanFileName T
_1
-- | 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 ::
  Member TDLib r =>
  -- | Path to the language pack database in which strings are stored 
  T ->
  -- | Localization target to which the language pack belongs 
  T ->
  -- | Language pack identifier 
  T ->
  -- | Language pack key of the string to be returned
  T ->
  Sem r (Error  LanguagePackStringValue)
getLanguagePackString :: T -> T -> T -> T -> Sem r (Error ∪ LanguagePackStringValue)
getLanguagePackString _1 :: T
_1 _2 :: T
_2 _3 :: T
_3 _4 :: T
_4 = GetLanguagePackString -> Sem r (Error ∪ LanguagePackStringValue)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLanguagePackString -> Sem r (Error ∪ LanguagePackStringValue))
-> GetLanguagePackString -> Sem r (Error ∪ LanguagePackStringValue)
forall a b. (a -> b) -> a -> b
$ T -> T -> T -> T -> GetLanguagePackString
GetLanguagePackString T
_1 T
_2 T
_3 T
_4
-- | Converts a JSON-serialized string to corresponding JsonValue object. This is an offline method. Can be called before authorization. Can be called synchronously 
getJsonValue ::
  Member TDLib r =>
  -- | The JSON-serialized string
  T ->
  Sem r (Error  JsonValue)
getJsonValue :: T -> Sem r (Error ∪ JsonValue)
getJsonValue _1 :: T
_1 = GetJsonValue -> Sem r (Error ∪ JsonValue)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetJsonValue -> Sem r (Error ∪ JsonValue))
-> GetJsonValue -> Sem r (Error ∪ JsonValue)
forall a b. (a -> b) -> a -> b
$ T -> GetJsonValue
GetJsonValue T
_1
-- | Converts a JsonValue object to corresponding JSON-serialized string. This is an offline method. Can be called before authorization. Can be called synchronously 
getJsonString ::
  Member TDLib r =>
  -- | The JsonValue object
  JsonValue ->
  Sem r (Error  Text)
getJsonString :: JsonValue -> Sem r (Error ∪ Text)
getJsonString _1 :: JsonValue
_1 = GetJsonString -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetJsonString -> Sem r (Error ∪ Text))
-> GetJsonString -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ JsonValue -> GetJsonString
GetJsonString JsonValue
_1
-- | Changes the user answer to a poll. A poll in quiz mode can be answered only once
setPollAnswer ::
  Member TDLib r =>
  -- | Identifier of the chat to which the poll belongs 
  I53 ->
  -- | Identifier of the message containing the poll
  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
  [I32] ->
  Sem r (Error  Ok)
setPollAnswer :: I32 -> I32 -> [I32] -> Sem r (Error ∪ Ok)
setPollAnswer _1 :: I32
_1 _2 :: I32
_2 _3 :: [I32]
_3 = SetPollAnswer -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetPollAnswer -> Sem r (Error ∪ Ok))
-> SetPollAnswer -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> [I32] -> SetPollAnswer
SetPollAnswer I32
_1 I32
_2 [I32]
_3
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to which the poll belongs 
  I53 ->
  -- | Identifier of the message containing the poll
  I53 ->
  -- | 0-based identifier of the answer option
  I32 ->
  -- | Number of users to skip in the result; must be non-negative
  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
  I32 ->
  Sem r (Error  Users)
getPollVoters :: I32 -> I32 -> I32 -> I32 -> I32 -> Sem r (Error ∪ Users)
getPollVoters _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: I32
_5 = GetPollVoters -> Sem r (Error ∪ Users)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPollVoters -> Sem r (Error ∪ Users))
-> GetPollVoters -> Sem r (Error ∪ Users)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> I32 -> I32 -> GetPollVoters
GetPollVoters I32
_1 I32
_2 I32
_3 I32
_4 I32
_5
-- | Stops a poll. A poll in a message can be stopped when the message has can_be_edited flag set
stopPoll ::
  Member TDLib r =>
  -- | Identifier of the chat to which the poll belongs 
  I53 ->
  -- | Identifier of the message containing the poll 
  I53 ->
  -- | The new message reply markup; for bots only
  ReplyMarkup ->
  Sem r (Error  Ok)
stopPoll :: I32 -> I32 -> ReplyMarkup -> Sem r (Error ∪ Ok)
stopPoll _1 :: I32
_1 _2 :: I32
_2 _3 :: ReplyMarkup
_3 = StopPoll -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (StopPoll -> Sem r (Error ∪ Ok)) -> StopPoll -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> ReplyMarkup -> StopPoll
StopPoll I32
_1 I32
_2 ReplyMarkup
_3
-- | Returns information about a button of type inlineKeyboardButtonTypeLoginUrl. The method needs to be called when the user presses the button
getLoginUrlInfo ::
  Member TDLib r =>
  -- | Chat identifier of the message with the button 
  I53 ->
  -- | Message identifier of the message with the button 
  I53 ->
  -- | Button identifier
  I32 ->
  Sem r (Error  LoginUrlInfo)
getLoginUrlInfo :: I32 -> I32 -> I32 -> Sem r (Error ∪ LoginUrlInfo)
getLoginUrlInfo _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = GetLoginUrlInfo -> Sem r (Error ∪ LoginUrlInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLoginUrlInfo -> Sem r (Error ∪ LoginUrlInfo))
-> GetLoginUrlInfo -> Sem r (Error ∪ LoginUrlInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> GetLoginUrlInfo
GetLoginUrlInfo I32
_1 I32
_2 I32
_3
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier of the message with the button 
  I53 ->
  -- | Message identifier of the message with the button 
  I53 ->
  -- | Button identifier
  I32 ->
  -- | True, if the user allowed the bot to send them messages
  Bool ->
  Sem r (Error  HttpUrl)
getLoginUrl :: I32 -> I32 -> I32 -> Bool -> Sem r (Error ∪ HttpUrl)
getLoginUrl _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: Bool
_4 = GetLoginUrl -> Sem r (Error ∪ HttpUrl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLoginUrl -> Sem r (Error ∪ HttpUrl))
-> GetLoginUrl -> Sem r (Error ∪ HttpUrl)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> Bool -> GetLoginUrl
GetLoginUrl I32
_1 I32
_2 I32
_3 Bool
_4
-- | 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 ::
  Member TDLib r =>
  -- | The identifier of the target bot
  I32 ->
  -- | Identifier of the chat where the query was sent 
  I53 ->
  -- | Location of the user, only if needed 
  Location ->
  -- | Text of the query 
  T ->
  -- | Offset of the first entry to return
  T ->
  Sem r (Error  InlineQueryResults)
getInlineQueryResults :: I32
-> I32 -> Location -> T -> T -> Sem r (Error ∪ InlineQueryResults)
getInlineQueryResults _1 :: I32
_1 _2 :: I32
_2 _3 :: Location
_3 _4 :: T
_4 _5 :: T
_5 = GetInlineQueryResults -> Sem r (Error ∪ InlineQueryResults)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetInlineQueryResults -> Sem r (Error ∪ InlineQueryResults))
-> GetInlineQueryResults -> Sem r (Error ∪ InlineQueryResults)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> Location -> T -> T -> GetInlineQueryResults
GetInlineQueryResults I32
_1 I32
_2 Location
_3 T
_4 T
_5
-- | Sets the result of an inline query; for bots only 
answerInlineQuery ::
  Member TDLib r =>
  -- | Identifier of the inline query 
  I64 ->
  -- | True, if the result of the query can be cached for the specified user
  Bool ->
  -- | The results of the query 
  [InputInlineQueryResult] ->
  -- | Allowed time to cache the results of the query, in seconds 
  I32 ->
  -- | Offset for the next inline query; pass an empty string if there are no more results
  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 
  T ->
  -- | The parameter for the bot start message
  T ->
  Sem r (Error  Ok)
answerInlineQuery :: I64
-> Bool
-> [InputInlineQueryResult]
-> I32
-> T
-> T
-> T
-> Sem r (Error ∪ Ok)
answerInlineQuery _1 :: I64
_1 _2 :: Bool
_2 _3 :: [InputInlineQueryResult]
_3 _4 :: I32
_4 _5 :: T
_5 _6 :: T
_6 _7 :: T
_7 = AnswerInlineQuery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AnswerInlineQuery -> Sem r (Error ∪ Ok))
-> AnswerInlineQuery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64
-> Bool
-> [InputInlineQueryResult]
-> I32
-> T
-> T
-> T
-> AnswerInlineQuery
AnswerInlineQuery I64
_1 Bool
_2 [InputInlineQueryResult]
_3 I32
_4 T
_5 T
_6 T
_7
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat with the message 
  I53 ->
  -- | Identifier of the message from which the query originated 
  I53 ->
  -- | Query payload
  CallbackQueryPayload ->
  Sem r (Error  CallbackQueryAnswer)
getCallbackQueryAnswer :: I32
-> I32
-> CallbackQueryPayload
-> Sem r (Error ∪ CallbackQueryAnswer)
getCallbackQueryAnswer _1 :: I32
_1 _2 :: I32
_2 _3 :: CallbackQueryPayload
_3 = GetCallbackQueryAnswer -> Sem r (Error ∪ CallbackQueryAnswer)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetCallbackQueryAnswer -> Sem r (Error ∪ CallbackQueryAnswer))
-> GetCallbackQueryAnswer -> Sem r (Error ∪ CallbackQueryAnswer)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> CallbackQueryPayload -> GetCallbackQueryAnswer
GetCallbackQueryAnswer I32
_1 I32
_2 CallbackQueryPayload
_3
-- | Sets the result of a callback query; for bots only 
answerCallbackQuery ::
  Member TDLib r =>
  -- | Identifier of the callback query 
  I64 ->
  -- | Text of the answer 
  T ->
  -- | If true, an alert should be shown to the user instead of a toast notification 
  Bool ->
  -- | URL to be opened 
  T ->
  -- | Time during which the result of the query can be cached, in seconds
  I32 ->
  Sem r (Error  Ok)
answerCallbackQuery :: I64 -> T -> Bool -> T -> I32 -> Sem r (Error ∪ Ok)
answerCallbackQuery _1 :: I64
_1 _2 :: T
_2 _3 :: Bool
_3 _4 :: T
_4 _5 :: I32
_5 = AnswerCallbackQuery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AnswerCallbackQuery -> Sem r (Error ∪ Ok))
-> AnswerCallbackQuery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> T -> Bool -> T -> I32 -> AnswerCallbackQuery
AnswerCallbackQuery I64
_1 T
_2 Bool
_3 T
_4 I32
_5
-- | Sets the result of a shipping query; for bots only 
answerShippingQuery ::
  Member TDLib r =>
  -- | Identifier of the shipping query 
  I64 ->
  -- | Available shipping options 
  [ShippingOption] ->
  -- | An error message, empty on success
  T ->
  Sem r (Error  Ok)
answerShippingQuery :: I64 -> [ShippingOption] -> T -> Sem r (Error ∪ Ok)
answerShippingQuery _1 :: I64
_1 _2 :: [ShippingOption]
_2 _3 :: T
_3 = AnswerShippingQuery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AnswerShippingQuery -> Sem r (Error ∪ Ok))
-> AnswerShippingQuery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> [ShippingOption] -> T -> AnswerShippingQuery
AnswerShippingQuery I64
_1 [ShippingOption]
_2 T
_3
-- | Sets the result of a pre-checkout query; for bots only 
answerPreCheckoutQuery ::
  Member TDLib r =>
  -- | Identifier of the pre-checkout query 
  I64 ->
  -- | An error message, empty on success
  T ->
  Sem r (Error  Ok)
answerPreCheckoutQuery :: I64 -> T -> Sem r (Error ∪ Ok)
answerPreCheckoutQuery _1 :: I64
_1 _2 :: T
_2 = AnswerPreCheckoutQuery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AnswerPreCheckoutQuery -> Sem r (Error ∪ Ok))
-> AnswerPreCheckoutQuery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> T -> AnswerPreCheckoutQuery
AnswerPreCheckoutQuery I64
_1 T
_2
-- | Updates the game score of the specified user in the game; for bots only 
setGameScore ::
  Member TDLib r =>
  -- | The chat to which the message with the game belongs 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | True, if the message should be edited 
  Bool ->
  -- | User identifier 
  I32 ->
  -- | The new 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
  Bool ->
  Sem r (Error  Message)
setGameScore :: I32 -> I32 -> Bool -> I32 -> I32 -> Bool -> Sem r (Error ∪ Message)
setGameScore _1 :: I32
_1 _2 :: I32
_2 _3 :: Bool
_3 _4 :: I32
_4 _5 :: I32
_5 _6 :: Bool
_6 = SetGameScore -> Sem r (Error ∪ Message)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetGameScore -> Sem r (Error ∪ Message))
-> SetGameScore -> Sem r (Error ∪ Message)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> Bool -> I32 -> I32 -> Bool -> SetGameScore
SetGameScore I32
_1 I32
_2 Bool
_3 I32
_4 I32
_5 Bool
_6
-- | Updates the game score of the specified user in a game; for bots only 
setInlineGameScore ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | True, if the message should be edited 
  Bool ->
  -- | User identifier 
  I32 ->
  -- | The new 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
  Bool ->
  Sem r (Error  Ok)
setInlineGameScore :: T -> Bool -> I32 -> I32 -> Bool -> Sem r (Error ∪ Ok)
setInlineGameScore _1 :: T
_1 _2 :: Bool
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: Bool
_5 = SetInlineGameScore -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetInlineGameScore -> Sem r (Error ∪ Ok))
-> SetInlineGameScore -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> Bool -> I32 -> I32 -> Bool -> SetInlineGameScore
SetInlineGameScore T
_1 Bool
_2 I32
_3 I32
_4 Bool
_5
-- | 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 ::
  Member TDLib r =>
  -- | The chat that contains the message with the game 
  I53 ->
  -- | Identifier of the message 
  I53 ->
  -- | User identifier
  I32 ->
  Sem r (Error  GameHighScores)
getGameHighScores :: I32 -> I32 -> I32 -> Sem r (Error ∪ GameHighScores)
getGameHighScores _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = GetGameHighScores -> Sem r (Error ∪ GameHighScores)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetGameHighScores -> Sem r (Error ∪ GameHighScores))
-> GetGameHighScores -> Sem r (Error ∪ GameHighScores)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> GetGameHighScores
GetGameHighScores I32
_1 I32
_2 I32
_3
-- | Returns game high scores and some part of the high score table in the range of the specified user; for bots only 
getInlineGameHighScores ::
  Member TDLib r =>
  -- | Inline message identifier 
  T ->
  -- | User identifier
  I32 ->
  Sem r (Error  GameHighScores)
getInlineGameHighScores :: T -> I32 -> Sem r (Error ∪ GameHighScores)
getInlineGameHighScores _1 :: T
_1 _2 :: I32
_2 = GetInlineGameHighScores -> Sem r (Error ∪ GameHighScores)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetInlineGameHighScores -> Sem r (Error ∪ GameHighScores))
-> GetInlineGameHighScores -> Sem r (Error ∪ GameHighScores)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> GetInlineGameHighScores
GetInlineGameHighScores T
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  -- | The message identifier of the used keyboard
  I53 ->
  Sem r (Error  Ok)
deleteChatReplyMarkup :: I32 -> I32 -> Sem r (Error ∪ Ok)
deleteChatReplyMarkup _1 :: I32
_1 _2 :: I32
_2 = DeleteChatReplyMarkup -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteChatReplyMarkup -> Sem r (Error ∪ Ok))
-> DeleteChatReplyMarkup -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> DeleteChatReplyMarkup
DeleteChatReplyMarkup I32
_1 I32
_2
-- | Sends a notification about user activity in a chat 
sendChatAction ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The action description
  ChatAction ->
  Sem r (Error  Ok)
sendChatAction :: I32 -> ChatAction -> Sem r (Error ∪ Ok)
sendChatAction _1 :: I32
_1 _2 :: ChatAction
_2 = SendChatAction -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendChatAction -> Sem r (Error ∪ Ok))
-> SendChatAction -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatAction -> SendChatAction
SendChatAction I32
_1 ChatAction
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
openChat :: I32 -> Sem r (Error ∪ Ok)
openChat _1 :: I32
_1 = OpenChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (OpenChat -> Sem r (Error ∪ Ok)) -> OpenChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> OpenChat
OpenChat I32
_1
-- | Informs TDLib that the chat is closed by the user. Many useful activities depend on the chat being opened or closed 
closeChat ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
closeChat :: I32 -> Sem r (Error ∪ Ok)
closeChat _1 :: I32
_1 = CloseChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CloseChat -> Sem r (Error ∪ Ok))
-> CloseChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> CloseChat
CloseChat I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The identifiers of the messages being viewed
  [I53] ->
  -- | True, if messages in closed chats should be marked as read
  Bool ->
  Sem r (Error  Ok)
viewMessages :: I32 -> [I32] -> Bool -> Sem r (Error ∪ Ok)
viewMessages _1 :: I32
_1 _2 :: [I32]
_2 _3 :: Bool
_3 = ViewMessages -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ViewMessages -> Sem r (Error ∪ Ok))
-> ViewMessages -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> [I32] -> Bool -> ViewMessages
ViewMessages I32
_1 [I32]
_2 Bool
_3
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier of the message 
  I53 ->
  -- | Identifier of the message with the opened content
  I53 ->
  Sem r (Error  Ok)
openMessageContent :: I32 -> I32 -> Sem r (Error ∪ Ok)
openMessageContent _1 :: I32
_1 _2 :: I32
_2 = OpenMessageContent -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (OpenMessageContent -> Sem r (Error ∪ Ok))
-> OpenMessageContent -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> OpenMessageContent
OpenMessageContent I32
_1 I32
_2
-- | Marks all mentions in a chat as read 
readAllChatMentions ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
readAllChatMentions :: I32 -> Sem r (Error ∪ Ok)
readAllChatMentions _1 :: I32
_1 = ReadAllChatMentions -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReadAllChatMentions -> Sem r (Error ∪ Ok))
-> ReadAllChatMentions -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ReadAllChatMentions
ReadAllChatMentions I32
_1
-- | Returns an existing chat corresponding to a given user 
createPrivateChat ::
  Member TDLib r =>
  -- | User identifier 
  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
  Bool ->
  Sem r (Error  Chat)
createPrivateChat :: I32 -> Bool -> Sem r (Error ∪ Chat)
createPrivateChat _1 :: I32
_1 _2 :: Bool
_2 = CreatePrivateChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreatePrivateChat -> Sem r (Error ∪ Chat))
-> CreatePrivateChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> CreatePrivateChat
CreatePrivateChat I32
_1 Bool
_2
-- | Returns an existing chat corresponding to a known basic group 
createBasicGroupChat ::
  Member TDLib r =>
  -- | Basic group identifier 
  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
  Bool ->
  Sem r (Error  Chat)
createBasicGroupChat :: I32 -> Bool -> Sem r (Error ∪ Chat)
createBasicGroupChat _1 :: I32
_1 _2 :: Bool
_2 = CreateBasicGroupChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateBasicGroupChat -> Sem r (Error ∪ Chat))
-> CreateBasicGroupChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> CreateBasicGroupChat
CreateBasicGroupChat I32
_1 Bool
_2
-- | Returns an existing chat corresponding to a known supergroup or channel 
createSupergroupChat ::
  Member TDLib r =>
  -- | Supergroup or channel identifier 
  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
  Bool ->
  Sem r (Error  Chat)
createSupergroupChat :: I32 -> Bool -> Sem r (Error ∪ Chat)
createSupergroupChat _1 :: I32
_1 _2 :: Bool
_2 = CreateSupergroupChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateSupergroupChat -> Sem r (Error ∪ Chat))
-> CreateSupergroupChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> CreateSupergroupChat
CreateSupergroupChat I32
_1 Bool
_2
-- | Returns an existing chat corresponding to a known secret chat 
createSecretChat ::
  Member TDLib r =>
  -- | Secret chat identifier
  I32 ->
  Sem r (Error  Chat)
createSecretChat :: I32 -> Sem r (Error ∪ Chat)
createSecretChat _1 :: I32
_1 = CreateSecretChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateSecretChat -> Sem r (Error ∪ Chat))
-> CreateSecretChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> CreateSecretChat
CreateSecretChat I32
_1
-- | Creates a new basic group and sends a corresponding messageBasicGroupChatCreate. Returns the newly created chat 
createNewBasicGroupChat ::
  Member TDLib r =>
  -- | Identifiers of users to be added to the basic group 
  [I32] ->
  -- | Title of the new basic group; 1-128 characters
  T ->
  Sem r (Error  Chat)
createNewBasicGroupChat :: [I32] -> T -> Sem r (Error ∪ Chat)
createNewBasicGroupChat _1 :: [I32]
_1 _2 :: T
_2 = CreateNewBasicGroupChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateNewBasicGroupChat -> Sem r (Error ∪ Chat))
-> CreateNewBasicGroupChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ [I32] -> T -> CreateNewBasicGroupChat
CreateNewBasicGroupChat [I32]
_1 T
_2
-- | Creates a new supergroup or channel and sends a corresponding messageSupergroupChatCreate. Returns the newly created chat 
createNewSupergroupChat ::
  Member TDLib r =>
  -- | Title of the new chat; 1-128 characters 
  T ->
  -- | True, if a channel chat should be created 
  Bool ->
  -- | Creates a new supergroup or channel and sends a corresponding messageSupergroupChatCreate. Returns the newly created chat 
  T ->
  -- | Chat location if a location-based supergroup is being created
  ChatLocation ->
  Sem r (Error  Chat)
createNewSupergroupChat :: T -> Bool -> T -> ChatLocation -> Sem r (Error ∪ Chat)
createNewSupergroupChat _1 :: T
_1 _2 :: Bool
_2 _3 :: T
_3 _4 :: ChatLocation
_4 = CreateNewSupergroupChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateNewSupergroupChat -> Sem r (Error ∪ Chat))
-> CreateNewSupergroupChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ T -> Bool -> T -> ChatLocation -> CreateNewSupergroupChat
CreateNewSupergroupChat T
_1 Bool
_2 T
_3 ChatLocation
_4
-- | Creates a new secret chat. Returns the newly created chat 
createNewSecretChat ::
  Member TDLib r =>
  -- | Identifier of the target user
  I32 ->
  Sem r (Error  Chat)
createNewSecretChat :: I32 -> Sem r (Error ∪ Chat)
createNewSecretChat _1 :: I32
_1 = CreateNewSecretChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateNewSecretChat -> Sem r (Error ∪ Chat))
-> CreateNewSecretChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> CreateNewSecretChat
CreateNewSecretChat I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the chat to upgrade
  I53 ->
  Sem r (Error  Chat)
upgradeBasicGroupChatToSupergroupChat :: I32 -> Sem r (Error ∪ Chat)
upgradeBasicGroupChatToSupergroupChat _1 :: I32
_1 = UpgradeBasicGroupChatToSupergroupChat -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (UpgradeBasicGroupChatToSupergroupChat -> Sem r (Error ∪ Chat))
-> UpgradeBasicGroupChatToSupergroupChat -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ I32 -> UpgradeBasicGroupChatToSupergroupChat
UpgradeBasicGroupChatToSupergroupChat I32
_1
-- | Returns chat lists to which the chat can be added. This is an offline request 
getChatListsToAddChat ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  ChatLists)
getChatListsToAddChat :: I32 -> Sem r (Error ∪ ChatLists)
getChatListsToAddChat _1 :: I32
_1 = GetChatListsToAddChat -> Sem r (Error ∪ ChatLists)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatListsToAddChat -> Sem r (Error ∪ ChatLists))
-> GetChatListsToAddChat -> Sem r (Error ∪ ChatLists)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChatListsToAddChat
GetChatListsToAddChat I32
_1
-- | Adds a chat to a chat list. A chat can't be simultaneously in Main and Archive chat lists, so it is automatically removed from another one if needed
addChatToList ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The chat list. Use getChatListsToAddChat to get suitable chat lists
  ChatList ->
  Sem r (Error  Ok)
addChatToList :: I32 -> ChatList -> Sem r (Error ∪ Ok)
addChatToList _1 :: I32
_1 _2 :: ChatList
_2 = AddChatToList -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddChatToList -> Sem r (Error ∪ Ok))
-> AddChatToList -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatList -> AddChatToList
AddChatToList I32
_1 ChatList
_2
-- | Returns information about a chat filter by its identifier 
getChatFilter ::
  Member TDLib r =>
  -- | Chat filter identifier
  I32 ->
  Sem r (Error  ChatFilter)
getChatFilter :: I32 -> Sem r (Error ∪ ChatFilter)
getChatFilter _1 :: I32
_1 = GetChatFilter -> Sem r (Error ∪ ChatFilter)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatFilter -> Sem r (Error ∪ ChatFilter))
-> GetChatFilter -> Sem r (Error ∪ ChatFilter)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChatFilter
GetChatFilter I32
_1
-- | Creates new chat filter. Returns information about the created chat filter 
createChatFilter ::
  Member TDLib r =>
  -- | Chat filter
  ChatFilter ->
  Sem r (Error  ChatFilterInfo)
createChatFilter :: ChatFilter -> Sem r (Error ∪ ChatFilterInfo)
createChatFilter _1 :: ChatFilter
_1 = CreateChatFilter -> Sem r (Error ∪ ChatFilterInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateChatFilter -> Sem r (Error ∪ ChatFilterInfo))
-> CreateChatFilter -> Sem r (Error ∪ ChatFilterInfo)
forall a b. (a -> b) -> a -> b
$ ChatFilter -> CreateChatFilter
CreateChatFilter ChatFilter
_1
-- | Edits existing chat filter. Returns information about the edited chat filter 
editChatFilter ::
  Member TDLib r =>
  -- | Chat filter identifier 
  I32 ->
  -- | The edited chat filter
  ChatFilter ->
  Sem r (Error  ChatFilterInfo)
editChatFilter :: I32 -> ChatFilter -> Sem r (Error ∪ ChatFilterInfo)
editChatFilter _1 :: I32
_1 _2 :: ChatFilter
_2 = EditChatFilter -> Sem r (Error ∪ ChatFilterInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditChatFilter -> Sem r (Error ∪ ChatFilterInfo))
-> EditChatFilter -> Sem r (Error ∪ ChatFilterInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatFilter -> EditChatFilter
EditChatFilter I32
_1 ChatFilter
_2
-- | Deletes existing chat filter 
deleteChatFilter ::
  Member TDLib r =>
  -- | Chat filter identifier
  I32 ->
  Sem r (Error  Ok)
deleteChatFilter :: I32 -> Sem r (Error ∪ Ok)
deleteChatFilter _1 :: I32
_1 = DeleteChatFilter -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteChatFilter -> Sem r (Error ∪ Ok))
-> DeleteChatFilter -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> DeleteChatFilter
DeleteChatFilter I32
_1
-- | Changes the order of chat filters 
reorderChatFilters ::
  Member TDLib r =>
  -- | Identifiers of chat filters in the new correct order
  [I32] ->
  Sem r (Error  Ok)
reorderChatFilters :: [I32] -> Sem r (Error ∪ Ok)
reorderChatFilters _1 :: [I32]
_1 = ReorderChatFilters -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReorderChatFilters -> Sem r (Error ∪ Ok))
-> ReorderChatFilters -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ [I32] -> ReorderChatFilters
ReorderChatFilters [I32]
_1
-- | Returns recommended chat filters for the current user
getRecommendedChatFilters ::
  Member TDLib r =>
  Sem r (Error  RecommendedChatFilters)
getRecommendedChatFilters :: Sem r (Error ∪ RecommendedChatFilters)
getRecommendedChatFilters  = GetRecommendedChatFilters -> Sem r (Error ∪ RecommendedChatFilters)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRecommendedChatFilters
 -> Sem r (Error ∪ RecommendedChatFilters))
-> GetRecommendedChatFilters
-> Sem r (Error ∪ RecommendedChatFilters)
forall a b. (a -> b) -> a -> b
$ GetRecommendedChatFilters
GetRecommendedChatFilters 
-- | Returns default icon name for a filter. This is an offline method. Can be called before authorization. Can be called synchronously 
getChatFilterDefaultIconName ::
  Member TDLib r =>
  -- | Chat filter
  ChatFilter ->
  Sem r (Error  Text)
getChatFilterDefaultIconName :: ChatFilter -> Sem r (Error ∪ Text)
getChatFilterDefaultIconName _1 :: ChatFilter
_1 = GetChatFilterDefaultIconName -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatFilterDefaultIconName -> Sem r (Error ∪ Text))
-> GetChatFilterDefaultIconName -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ ChatFilter -> GetChatFilterDefaultIconName
GetChatFilterDefaultIconName ChatFilter
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New title of the chat; 1-128 characters
  T ->
  Sem r (Error  Ok)
setChatTitle :: I32 -> T -> Sem r (Error ∪ Ok)
setChatTitle _1 :: I32
_1 _2 :: T
_2 = SetChatTitle -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatTitle -> Sem r (Error ∪ Ok))
-> SetChatTitle -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SetChatTitle
SetChatTitle I32
_1 T
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  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
  InputFile ->
  Sem r (Error  Ok)
setChatPhoto :: I32 -> InputFile -> Sem r (Error ∪ Ok)
setChatPhoto _1 :: I32
_1 _2 :: InputFile
_2 = SetChatPhoto -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatPhoto -> Sem r (Error ∪ Ok))
-> SetChatPhoto -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> InputFile -> SetChatPhoto
SetChatPhoto I32
_1 InputFile
_2
-- | Changes the chat members permissions. Supported only for basic groups and supergroups. Requires can_restrict_members administrator right
setChatPermissions ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New non-administrator members permissions in the chat
  ChatPermissions ->
  Sem r (Error  Ok)
setChatPermissions :: I32 -> ChatPermissions -> Sem r (Error ∪ Ok)
setChatPermissions _1 :: I32
_1 _2 :: ChatPermissions
_2 = SetChatPermissions -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatPermissions -> Sem r (Error ∪ Ok))
-> SetChatPermissions -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatPermissions -> SetChatPermissions
SetChatPermissions I32
_1 ChatPermissions
_2
-- | Changes the draft message in a chat 
setChatDraftMessage ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New draft message; may be null
  (Maybe) (DraftMessage) ->
  Sem r (Error  Ok)
setChatDraftMessage :: I32 -> Maybe DraftMessage -> Sem r (Error ∪ Ok)
setChatDraftMessage _1 :: I32
_1 _2 :: Maybe DraftMessage
_2 = SetChatDraftMessage -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatDraftMessage -> Sem r (Error ∪ Ok))
-> SetChatDraftMessage -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Maybe DraftMessage -> SetChatDraftMessage
SetChatDraftMessage I32
_1 Maybe DraftMessage
_2
-- | Changes the notification settings of a chat. Notification settings of a chat with the current user (Saved Messages) can't be changed
setChatNotificationSettings ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New notification settings for the chat. If the chat is muted for more than 1 week, it is considered to be muted forever
  ChatNotificationSettings ->
  Sem r (Error  Ok)
setChatNotificationSettings :: I32 -> ChatNotificationSettings -> Sem r (Error ∪ Ok)
setChatNotificationSettings _1 :: I32
_1 _2 :: ChatNotificationSettings
_2 = SetChatNotificationSettings -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatNotificationSettings -> Sem r (Error ∪ Ok))
-> SetChatNotificationSettings -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatNotificationSettings -> SetChatNotificationSettings
SetChatNotificationSettings I32
_1 ChatNotificationSettings
_2
-- | Changes the marked as unread state of a chat 
toggleChatIsMarkedAsUnread ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New value of is_marked_as_unread
  Bool ->
  Sem r (Error  Ok)
toggleChatIsMarkedAsUnread :: I32 -> Bool -> Sem r (Error ∪ Ok)
toggleChatIsMarkedAsUnread _1 :: I32
_1 _2 :: Bool
_2 = ToggleChatIsMarkedAsUnread -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ToggleChatIsMarkedAsUnread -> Sem r (Error ∪ Ok))
-> ToggleChatIsMarkedAsUnread -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> ToggleChatIsMarkedAsUnread
ToggleChatIsMarkedAsUnread I32
_1 Bool
_2
-- | Changes the value of the default disable_notification parameter, used when a message is sent to a chat 
toggleChatDefaultDisableNotification ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New value of default_disable_notification
  Bool ->
  Sem r (Error  Ok)
toggleChatDefaultDisableNotification :: I32 -> Bool -> Sem r (Error ∪ Ok)
toggleChatDefaultDisableNotification _1 :: I32
_1 _2 :: Bool
_2 = ToggleChatDefaultDisableNotification -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ToggleChatDefaultDisableNotification -> Sem r (Error ∪ Ok))
-> ToggleChatDefaultDisableNotification -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> ToggleChatDefaultDisableNotification
ToggleChatDefaultDisableNotification I32
_1 Bool
_2
-- | Changes client data associated with a chat 
setChatClientData ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New value of client_data
  T ->
  Sem r (Error  Ok)
setChatClientData :: I32 -> T -> Sem r (Error ∪ Ok)
setChatClientData _1 :: I32
_1 _2 :: T
_2 = SetChatClientData -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatClientData -> Sem r (Error ∪ Ok))
-> SetChatClientData -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SetChatClientData
SetChatClientData I32
_1 T
_2
-- | Changes information about a chat. Available for basic groups, supergroups, and channels. Requires can_change_info rights 
setChatDescription ::
  Member TDLib r =>
  -- | Identifier of the chat 
  I53 ->
  -- | Changes information about a chat. Available for basic groups, supergroups, and channels. Requires can_change_info rights 
  T ->
  Sem r (Error  Ok)
setChatDescription :: I32 -> T -> Sem r (Error ∪ Ok)
setChatDescription _1 :: I32
_1 _2 :: T
_2 = SetChatDescription -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatDescription -> Sem r (Error ∪ Ok))
-> SetChatDescription -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SetChatDescription
SetChatDescription I32
_1 T
_2
-- | Changes the discussion group of a channel chat; requires can_change_info rights in the channel if it is specified 
setChatDiscussionGroup ::
  Member TDLib r =>
  -- | 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) 
  I53 ->
  -- | Identifier of a new channel's discussion group. Use 0 to remove the discussion group.
  I53 ->
  Sem r (Error  Ok)
setChatDiscussionGroup :: I32 -> I32 -> Sem r (Error ∪ Ok)
setChatDiscussionGroup _1 :: I32
_1 _2 :: I32
_2 = SetChatDiscussionGroup -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatDiscussionGroup -> Sem r (Error ∪ Ok))
-> SetChatDiscussionGroup -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> SetChatDiscussionGroup
SetChatDiscussionGroup I32
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New location for the chat; must be valid and not null
  ChatLocation ->
  Sem r (Error  Ok)
setChatLocation :: I32 -> ChatLocation -> Sem r (Error ∪ Ok)
setChatLocation _1 :: I32
_1 _2 :: ChatLocation
_2 = SetChatLocation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatLocation -> Sem r (Error ∪ Ok))
-> SetChatLocation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatLocation -> SetChatLocation
SetChatLocation I32
_1 ChatLocation
_2
-- | Changes the slow mode delay of a chat. Available only for supergroups; requires can_restrict_members rights 
setChatSlowModeDelay ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | New slow mode delay for the chat; must be one of 0, 10, 30, 60, 300, 900, 3600
  I32 ->
  Sem r (Error  Ok)
setChatSlowModeDelay :: I32 -> I32 -> Sem r (Error ∪ Ok)
setChatSlowModeDelay _1 :: I32
_1 _2 :: I32
_2 = SetChatSlowModeDelay -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatSlowModeDelay -> Sem r (Error ∪ Ok))
-> SetChatSlowModeDelay -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> SetChatSlowModeDelay
SetChatSlowModeDelay I32
_1 I32
_2
-- | Pins a message in a chat; requires can_pin_messages rights 
pinChatMessage ::
  Member TDLib r =>
  -- | Identifier of the chat 
  I53 ->
  -- | Identifier of the new pinned message 
  I53 ->
  -- | True, if there should be no notification about the pinned message
  Bool ->
  Sem r (Error  Ok)
pinChatMessage :: I32 -> I32 -> Bool -> Sem r (Error ∪ Ok)
pinChatMessage _1 :: I32
_1 _2 :: I32
_2 _3 :: Bool
_3 = PinChatMessage -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (PinChatMessage -> Sem r (Error ∪ Ok))
-> PinChatMessage -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> Bool -> PinChatMessage
PinChatMessage I32
_1 I32
_2 Bool
_3
-- | Removes the pinned message from a chat; requires can_pin_messages rights in the group or channel 
unpinChatMessage ::
  Member TDLib r =>
  -- | Identifier of the chat
  I53 ->
  Sem r (Error  Ok)
unpinChatMessage :: I32 -> Sem r (Error ∪ Ok)
unpinChatMessage _1 :: I32
_1 = UnpinChatMessage -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (UnpinChatMessage -> Sem r (Error ∪ Ok))
-> UnpinChatMessage -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> UnpinChatMessage
UnpinChatMessage I32
_1
-- | Adds current user as a new member to a chat. Private and secret chats can't be joined using this method 
joinChat ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
joinChat :: I32 -> Sem r (Error ∪ Ok)
joinChat _1 :: I32
_1 = JoinChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (JoinChat -> Sem r (Error ∪ Ok)) -> JoinChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> JoinChat
JoinChat I32
_1
-- | Removes current user from chat members. Private and secret chats can't be left using this method 
leaveChat ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
leaveChat :: I32 -> Sem r (Error ∪ Ok)
leaveChat _1 :: I32
_1 = LeaveChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (LeaveChat -> Sem r (Error ∪ Ok))
-> LeaveChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> LeaveChat
LeaveChat I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Identifier of the user 
  I32 ->
  -- | The number of earlier messages from the chat to be forwarded to the new member; up to 100. Ignored for supergroups and channels
  I32 ->
  Sem r (Error  Ok)
addChatMember :: I32 -> I32 -> I32 -> Sem r (Error ∪ Ok)
addChatMember _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = AddChatMember -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddChatMember -> Sem r (Error ∪ Ok))
-> AddChatMember -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> AddChatMember
AddChatMember I32
_1 I32
_2 I32
_3
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Identifiers of the users to be added to the chat
  [I32] ->
  Sem r (Error  Ok)
addChatMembers :: I32 -> [I32] -> Sem r (Error ∪ Ok)
addChatMembers _1 :: I32
_1 _2 :: [I32]
_2 = AddChatMembers -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddChatMembers -> Sem r (Error ∪ Ok))
-> AddChatMembers -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> [I32] -> AddChatMembers
AddChatMembers I32
_1 [I32]
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | User identifier 
  I32 ->
  -- | The new status of the member in the chat
  ChatMemberStatus ->
  Sem r (Error  Ok)
setChatMemberStatus :: I32 -> I32 -> ChatMemberStatus -> Sem r (Error ∪ Ok)
setChatMemberStatus _1 :: I32
_1 _2 :: I32
_2 _3 :: ChatMemberStatus
_3 = SetChatMemberStatus -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetChatMemberStatus -> Sem r (Error ∪ Ok))
-> SetChatMemberStatus -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> ChatMemberStatus -> SetChatMemberStatus
SetChatMemberStatus I32
_1 I32
_2 ChatMemberStatus
_3
-- | Checks whether the current session can be used to transfer a chat ownership to another user
canTransferOwnership ::
  Member TDLib r =>
  Sem r (Error  CanTransferOwnershipResult)
canTransferOwnership :: Sem r (Error ∪ CanTransferOwnershipResult)
canTransferOwnership  = CanTransferOwnership -> Sem r (Error ∪ CanTransferOwnershipResult)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CanTransferOwnership
 -> Sem r (Error ∪ CanTransferOwnershipResult))
-> CanTransferOwnership
-> Sem r (Error ∪ CanTransferOwnershipResult)
forall a b. (a -> b) -> a -> b
$ CanTransferOwnership
CanTransferOwnership 
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Identifier of the user to which transfer the ownership. The ownership can't be transferred to a bot or to a deleted user 
  I32 ->
  -- | The password of the current user
  T ->
  Sem r (Error  Ok)
transferChatOwnership :: I32 -> I32 -> T -> Sem r (Error ∪ Ok)
transferChatOwnership _1 :: I32
_1 _2 :: I32
_2 _3 :: T
_3 = TransferChatOwnership -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TransferChatOwnership -> Sem r (Error ∪ Ok))
-> TransferChatOwnership -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> T -> TransferChatOwnership
TransferChatOwnership I32
_1 I32
_2 T
_3
-- | Returns information about a single member of a chat 
getChatMember ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | User identifier
  I32 ->
  Sem r (Error  ChatMember)
getChatMember :: I32 -> I32 -> Sem r (Error ∪ ChatMember)
getChatMember _1 :: I32
_1 _2 :: I32
_2 = GetChatMember -> Sem r (Error ∪ ChatMember)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatMember -> Sem r (Error ∪ ChatMember))
-> GetChatMember -> Sem r (Error ∪ ChatMember)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetChatMember
GetChatMember I32
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Query to search for 
  T ->
  -- | The maximum number of users to be returned 
  I32 ->
  -- | The type of users to return. By default, chatMembersFilterMembers
  ChatMembersFilter ->
  Sem r (Error  ChatMembers)
searchChatMembers :: I32 -> T -> I32 -> ChatMembersFilter -> Sem r (Error ∪ ChatMembers)
searchChatMembers _1 :: I32
_1 _2 :: T
_2 _3 :: I32
_3 _4 :: ChatMembersFilter
_4 = SearchChatMembers -> Sem r (Error ∪ ChatMembers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchChatMembers -> Sem r (Error ∪ ChatMembers))
-> SearchChatMembers -> Sem r (Error ∪ ChatMembers)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> I32 -> ChatMembersFilter -> SearchChatMembers
SearchChatMembers I32
_1 T
_2 I32
_3 ChatMembersFilter
_4
-- | Returns a list of administrators of the chat with their custom titles 
getChatAdministrators ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  ChatAdministrators)
getChatAdministrators :: I32 -> Sem r (Error ∪ ChatAdministrators)
getChatAdministrators _1 :: I32
_1 = GetChatAdministrators -> Sem r (Error ∪ ChatAdministrators)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatAdministrators -> Sem r (Error ∪ ChatAdministrators))
-> GetChatAdministrators -> Sem r (Error ∪ ChatAdministrators)
forall a b. (a -> b) -> a -> b
$ I32 -> GetChatAdministrators
GetChatAdministrators I32
_1
-- | Clears draft messages in all chats 
clearAllDraftMessages ::
  Member TDLib r =>
  -- | If true, local draft messages in secret chats will not be cleared
  Bool ->
  Sem r (Error  Ok)
clearAllDraftMessages :: Bool -> Sem r (Error ∪ Ok)
clearAllDraftMessages _1 :: Bool
_1 = ClearAllDraftMessages -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ClearAllDraftMessages -> Sem r (Error ∪ Ok))
-> ClearAllDraftMessages -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Bool -> ClearAllDraftMessages
ClearAllDraftMessages Bool
_1
-- | Returns list of chats with non-default notification settings 
getChatNotificationSettingsExceptions ::
  Member TDLib r =>
  -- | If specified, only chats from the specified scope will be returned 
  NotificationSettingsScope ->
  -- | If true, also chats with non-default sound will be returned
  Bool ->
  Sem r (Error  Chats)
getChatNotificationSettingsExceptions :: NotificationSettingsScope -> Bool -> Sem r (Error ∪ Chats)
getChatNotificationSettingsExceptions _1 :: NotificationSettingsScope
_1 _2 :: Bool
_2 = GetChatNotificationSettingsExceptions -> Sem r (Error ∪ Chats)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatNotificationSettingsExceptions -> Sem r (Error ∪ Chats))
-> GetChatNotificationSettingsExceptions -> Sem r (Error ∪ Chats)
forall a b. (a -> b) -> a -> b
$ NotificationSettingsScope
-> Bool -> GetChatNotificationSettingsExceptions
GetChatNotificationSettingsExceptions NotificationSettingsScope
_1 Bool
_2
-- | Returns the notification settings for chats of a given type 
getScopeNotificationSettings ::
  Member TDLib r =>
  -- | Types of chats for which to return the notification settings information
  NotificationSettingsScope ->
  Sem r (Error  ScopeNotificationSettings)
getScopeNotificationSettings :: NotificationSettingsScope
-> Sem r (Error ∪ ScopeNotificationSettings)
getScopeNotificationSettings _1 :: NotificationSettingsScope
_1 = GetScopeNotificationSettings
-> Sem r (Error ∪ ScopeNotificationSettings)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetScopeNotificationSettings
 -> Sem r (Error ∪ ScopeNotificationSettings))
-> GetScopeNotificationSettings
-> Sem r (Error ∪ ScopeNotificationSettings)
forall a b. (a -> b) -> a -> b
$ NotificationSettingsScope -> GetScopeNotificationSettings
GetScopeNotificationSettings NotificationSettingsScope
_1
-- | Changes notification settings for chats of a given type 
setScopeNotificationSettings ::
  Member TDLib r =>
  -- | Types of chats for which to change the notification settings 
  NotificationSettingsScope ->
  -- | The new notification settings for the given scope
  ScopeNotificationSettings ->
  Sem r (Error  Ok)
setScopeNotificationSettings :: NotificationSettingsScope
-> ScopeNotificationSettings -> Sem r (Error ∪ Ok)
setScopeNotificationSettings _1 :: NotificationSettingsScope
_1 _2 :: ScopeNotificationSettings
_2 = SetScopeNotificationSettings -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetScopeNotificationSettings -> Sem r (Error ∪ Ok))
-> SetScopeNotificationSettings -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ NotificationSettingsScope
-> ScopeNotificationSettings -> SetScopeNotificationSettings
SetScopeNotificationSettings NotificationSettingsScope
_1 ScopeNotificationSettings
_2
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  Ok)
resetAllNotificationSettings :: Sem r (Error ∪ Ok)
resetAllNotificationSettings  = ResetAllNotificationSettings -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResetAllNotificationSettings -> Sem r (Error ∪ Ok))
-> ResetAllNotificationSettings -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ResetAllNotificationSettings
ResetAllNotificationSettings 
-- | 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/arhive chat list
toggleChatIsPinned ::
  Member TDLib r =>
  -- | Chat list in which to change the pinned state of the chat 
  ChatList ->
  -- | Chat identifier 
  I53 ->
  -- | True, if the chat is pinned
  Bool ->
  Sem r (Error  Ok)
toggleChatIsPinned :: ChatList -> I32 -> Bool -> Sem r (Error ∪ Ok)
toggleChatIsPinned _1 :: ChatList
_1 _2 :: I32
_2 _3 :: Bool
_3 = ToggleChatIsPinned -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ToggleChatIsPinned -> Sem r (Error ∪ Ok))
-> ToggleChatIsPinned -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ChatList -> I32 -> Bool -> ToggleChatIsPinned
ToggleChatIsPinned ChatList
_1 I32
_2 Bool
_3
-- | Changes the order of pinned chats 
setPinnedChats ::
  Member TDLib r =>
  -- | Chat list in which to change the order of pinned chats 
  ChatList ->
  -- | The new list of pinned chats
  [I53] ->
  Sem r (Error  Ok)
setPinnedChats :: ChatList -> [I32] -> Sem r (Error ∪ Ok)
setPinnedChats _1 :: ChatList
_1 _2 :: [I32]
_2 = SetPinnedChats -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetPinnedChats -> Sem r (Error ∪ Ok))
-> SetPinnedChats -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ChatList -> [I32] -> SetPinnedChats
SetPinnedChats ChatList
_1 [I32]
_2
-- | Downloads a file from the cloud. Download progress and completion of the download will be notified through updateFile updates
downloadFile ::
  Member TDLib r =>
  -- | Identifier of the file to download
  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
  I32 ->
  -- | The starting position from which the file should be downloaded
  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
  I32 ->
  -- | If false, this request returns file state just after the download has been started. If true, this request returns file state only after
  Bool ->
  Sem r (Error  File)
downloadFile :: I32 -> I32 -> I32 -> I32 -> Bool -> Sem r (Error ∪ File)
downloadFile _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: Bool
_5 = DownloadFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DownloadFile -> Sem r (Error ∪ File))
-> DownloadFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> I32 -> Bool -> DownloadFile
DownloadFile I32
_1 I32
_2 I32
_3 I32
_4 Bool
_5
-- | Returns file downloaded prefix size from a given offset 
getFileDownloadedPrefixSize ::
  Member TDLib r =>
  -- | Identifier of the file 
  I32 ->
  -- | Offset from which downloaded prefix size should be calculated
  I32 ->
  Sem r (Error  Count)
getFileDownloadedPrefixSize :: I32 -> I32 -> Sem r (Error ∪ Count)
getFileDownloadedPrefixSize _1 :: I32
_1 _2 :: I32
_2 = GetFileDownloadedPrefixSize -> Sem r (Error ∪ Count)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetFileDownloadedPrefixSize -> Sem r (Error ∪ Count))
-> GetFileDownloadedPrefixSize -> Sem r (Error ∪ Count)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetFileDownloadedPrefixSize
GetFileDownloadedPrefixSize I32
_1 I32
_2
-- | Stops the downloading of a file. If a file has already been downloaded, does nothing 
cancelDownloadFile ::
  Member TDLib r =>
  -- | Identifier of a file to stop downloading 
  I32 ->
  -- | Pass true to stop downloading only if it hasn't been started, i.e. request hasn't been sent to server
  Bool ->
  Sem r (Error  Ok)
cancelDownloadFile :: I32 -> Bool -> Sem r (Error ∪ Ok)
cancelDownloadFile _1 :: I32
_1 _2 :: Bool
_2 = CancelDownloadFile -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CancelDownloadFile -> Sem r (Error ∪ Ok))
-> CancelDownloadFile -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> CancelDownloadFile
CancelDownloadFile I32
_1 Bool
_2
-- | 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 ::
  Member TDLib r =>
  -- | File to upload 
  InputFile ->
  -- | 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
  I32 ->
  Sem r (Error  File)
uploadFile :: InputFile -> FileType -> I32 -> Sem r (Error ∪ File)
uploadFile _1 :: InputFile
_1 _2 :: FileType
_2 _3 :: I32
_3 = UploadFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (UploadFile -> Sem r (Error ∪ File))
-> UploadFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ InputFile -> FileType -> I32 -> UploadFile
UploadFile InputFile
_1 FileType
_2 I32
_3
-- | Stops the uploading of a file. Supported only for files uploaded by using uploadFile. For other files the behavior is undefined 
cancelUploadFile ::
  Member TDLib r =>
  -- | Identifier of the file to stop uploading
  I32 ->
  Sem r (Error  Ok)
cancelUploadFile :: I32 -> Sem r (Error ∪ Ok)
cancelUploadFile _1 :: I32
_1 = CancelUploadFile -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CancelUploadFile -> Sem r (Error ∪ Ok))
-> CancelUploadFile -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> CancelUploadFile
CancelUploadFile I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | The identifier of the generation process 
  I64 ->
  -- | The offset from which to write the data to the file 
  I32 ->
  -- | The data to write
  ByteString64 ->
  Sem r (Error  Ok)
writeGeneratedFilePart :: I64 -> I32 -> ByteString64 -> Sem r (Error ∪ Ok)
writeGeneratedFilePart _1 :: I64
_1 _2 :: I32
_2 _3 :: ByteString64
_3 = WriteGeneratedFilePart -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (WriteGeneratedFilePart -> Sem r (Error ∪ Ok))
-> WriteGeneratedFilePart -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> I32 -> ByteString64 -> WriteGeneratedFilePart
WriteGeneratedFilePart I64
_1 I32
_2 ByteString64
_3
-- | Informs TDLib on a file generation progress
setFileGenerationProgress ::
  Member TDLib r =>
  -- | The identifier of the generation process
  I64 ->
  -- | Expected size of the generated file, in bytes; 0 if unknown
  I32 ->
  -- | The number of bytes already generated
  I32 ->
  Sem r (Error  Ok)
setFileGenerationProgress :: I64 -> I32 -> I32 -> Sem r (Error ∪ Ok)
setFileGenerationProgress _1 :: I64
_1 _2 :: I32
_2 _3 :: I32
_3 = SetFileGenerationProgress -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetFileGenerationProgress -> Sem r (Error ∪ Ok))
-> SetFileGenerationProgress -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> I32 -> I32 -> SetFileGenerationProgress
SetFileGenerationProgress I64
_1 I32
_2 I32
_3
-- | Finishes the file generation
finishFileGeneration ::
  Member TDLib r =>
  -- | The identifier of the generation process
  I64 ->
  -- | If set, means that file generation has failed and should be terminated
  Error ->
  Sem r (Error  Ok)
finishFileGeneration :: I64 -> Error -> Sem r (Error ∪ Ok)
finishFileGeneration _1 :: I64
_1 _2 :: Error
_2 = FinishFileGeneration -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (FinishFileGeneration -> Sem r (Error ∪ Ok))
-> FinishFileGeneration -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> Error -> FinishFileGeneration
FinishFileGeneration I64
_1 Error
_2
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the file. The file must be located in the TDLib file cache
  I32 ->
  -- | The offset from which to read the file
  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
  I32 ->
  Sem r (Error  FilePart)
readFilePart :: I32 -> I32 -> I32 -> Sem r (Error ∪ FilePart)
readFilePart _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = ReadFilePart -> Sem r (Error ∪ FilePart)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReadFilePart -> Sem r (Error ∪ FilePart))
-> ReadFilePart -> Sem r (Error ∪ FilePart)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> ReadFilePart
ReadFilePart I32
_1 I32
_2 I32
_3
-- | Deletes a file from the TDLib file cache 
deleteFile ::
  Member TDLib r =>
  -- | Identifier of the file to delete
  I32 ->
  Sem r (Error  Ok)
deleteFile :: I32 -> Sem r (Error ∪ Ok)
deleteFile _1 :: I32
_1 = DeleteFile -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteFile -> Sem r (Error ∪ Ok))
-> DeleteFile -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> DeleteFile
DeleteFile I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  ChatInviteLink)
generateChatInviteLink :: I32 -> Sem r (Error ∪ ChatInviteLink)
generateChatInviteLink _1 :: I32
_1 = GenerateChatInviteLink -> Sem r (Error ∪ ChatInviteLink)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GenerateChatInviteLink -> Sem r (Error ∪ ChatInviteLink))
-> GenerateChatInviteLink -> Sem r (Error ∪ ChatInviteLink)
forall a b. (a -> b) -> a -> b
$ I32 -> GenerateChatInviteLink
GenerateChatInviteLink I32
_1
-- | Checks the validity of an invite link for a chat and returns information about the corresponding chat 
checkChatInviteLink ::
  Member TDLib r =>
  -- | Invite link to be checked; should begin with "https://t.me/joinchat/", "https://telegram.me/joinchat/", or "https://telegram.dog/joinchat/"
  T ->
  Sem r (Error  ChatInviteLinkInfo)
checkChatInviteLink :: T -> Sem r (Error ∪ ChatInviteLinkInfo)
checkChatInviteLink _1 :: T
_1 = CheckChatInviteLink -> Sem r (Error ∪ ChatInviteLinkInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckChatInviteLink -> Sem r (Error ∪ ChatInviteLinkInfo))
-> CheckChatInviteLink -> Sem r (Error ∪ ChatInviteLinkInfo)
forall a b. (a -> b) -> a -> b
$ T -> CheckChatInviteLink
CheckChatInviteLink T
_1
-- | 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 ::
  Member TDLib r =>
  -- | Invite link to import; should begin with "https://t.me/joinchat/", "https://telegram.me/joinchat/", or "https://telegram.dog/joinchat/"
  T ->
  Sem r (Error  Chat)
joinChatByInviteLink :: T -> Sem r (Error ∪ Chat)
joinChatByInviteLink _1 :: T
_1 = JoinChatByInviteLink -> Sem r (Error ∪ Chat)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (JoinChatByInviteLink -> Sem r (Error ∪ Chat))
-> JoinChatByInviteLink -> Sem r (Error ∪ Chat)
forall a b. (a -> b) -> a -> b
$ T -> JoinChatByInviteLink
JoinChatByInviteLink T
_1
-- | Creates a new call 
createCall ::
  Member TDLib r =>
  -- | Identifier of the user to be called 
  I32 ->
  -- | Description of the call protocols supported by the client
  CallProtocol ->
  Sem r (Error  CallId)
createCall :: I32 -> CallProtocol -> Sem r (Error ∪ CallId)
createCall _1 :: I32
_1 _2 :: CallProtocol
_2 = CreateCall -> Sem r (Error ∪ CallId)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateCall -> Sem r (Error ∪ CallId))
-> CreateCall -> Sem r (Error ∪ CallId)
forall a b. (a -> b) -> a -> b
$ I32 -> CallProtocol -> CreateCall
CreateCall I32
_1 CallProtocol
_2
-- | Accepts an incoming call 
acceptCall ::
  Member TDLib r =>
  -- | Call identifier 
  I32 ->
  -- | Description of the call protocols supported by the client
  CallProtocol ->
  Sem r (Error  Ok)
acceptCall :: I32 -> CallProtocol -> Sem r (Error ∪ Ok)
acceptCall _1 :: I32
_1 _2 :: CallProtocol
_2 = AcceptCall -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AcceptCall -> Sem r (Error ∪ Ok))
-> AcceptCall -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> CallProtocol -> AcceptCall
AcceptCall I32
_1 CallProtocol
_2
-- | Discards a call 
discardCall ::
  Member TDLib r =>
  -- | Call identifier 
  I32 ->
  -- | True, if the user was disconnected 
  Bool ->
  -- | The call duration, in seconds 
  I32 ->
  -- | Identifier of the connection used during the call
  I64 ->
  Sem r (Error  Ok)
discardCall :: I32 -> Bool -> I32 -> I64 -> Sem r (Error ∪ Ok)
discardCall _1 :: I32
_1 _2 :: Bool
_2 _3 :: I32
_3 _4 :: I64
_4 = DiscardCall -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DiscardCall -> Sem r (Error ∪ Ok))
-> DiscardCall -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> I32 -> I64 -> DiscardCall
DiscardCall I32
_1 Bool
_2 I32
_3 I64
_4
-- | Sends a call rating 
sendCallRating ::
  Member TDLib r =>
  -- | Call identifier 
  I32 ->
  -- | Call rating; 1-5 
  I32 ->
  -- | An optional user comment if the rating is less than 5 
  T ->
  -- | List of the exact types of problems with the call, specified by the user
  [CallProblem] ->
  Sem r (Error  Ok)
sendCallRating :: I32 -> I32 -> T -> [CallProblem] -> Sem r (Error ∪ Ok)
sendCallRating _1 :: I32
_1 _2 :: I32
_2 _3 :: T
_3 _4 :: [CallProblem]
_4 = SendCallRating -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendCallRating -> Sem r (Error ∪ Ok))
-> SendCallRating -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> T -> [CallProblem] -> SendCallRating
SendCallRating I32
_1 I32
_2 T
_3 [CallProblem]
_4
-- | Sends debug information for a call 
sendCallDebugInformation ::
  Member TDLib r =>
  -- | Call identifier 
  I32 ->
  -- | Debug information in application-specific format
  T ->
  Sem r (Error  Ok)
sendCallDebugInformation :: I32 -> T -> Sem r (Error ∪ Ok)
sendCallDebugInformation _1 :: I32
_1 _2 :: T
_2 = SendCallDebugInformation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendCallDebugInformation -> Sem r (Error ∪ Ok))
-> SendCallDebugInformation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SendCallDebugInformation
SendCallDebugInformation I32
_1 T
_2
-- | Adds a user to the blacklist 
blockUser ::
  Member TDLib r =>
  -- | User identifier
  I32 ->
  Sem r (Error  Ok)
blockUser :: I32 -> Sem r (Error ∪ Ok)
blockUser _1 :: I32
_1 = BlockUser -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (BlockUser -> Sem r (Error ∪ Ok))
-> BlockUser -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> BlockUser
BlockUser I32
_1
-- | Removes a user from the blacklist 
unblockUser ::
  Member TDLib r =>
  -- | User identifier
  I32 ->
  Sem r (Error  Ok)
unblockUser :: I32 -> Sem r (Error ∪ Ok)
unblockUser _1 :: I32
_1 = UnblockUser -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (UnblockUser -> Sem r (Error ∪ Ok))
-> UnblockUser -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> UnblockUser
UnblockUser I32
_1
-- | Returns users that were blocked by the current user 
getBlockedUsers ::
  Member TDLib r =>
  -- | Number of users to skip in the result; must be non-negative 
  I32 ->
  -- | The maximum number of users to return; up to 100
  I32 ->
  Sem r (Error  Users)
getBlockedUsers :: I32 -> I32 -> Sem r (Error ∪ Users)
getBlockedUsers _1 :: I32
_1 _2 :: I32
_2 = GetBlockedUsers -> Sem r (Error ∪ Users)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBlockedUsers -> Sem r (Error ∪ Users))
-> GetBlockedUsers -> Sem r (Error ∪ Users)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetBlockedUsers
GetBlockedUsers I32
_1 I32
_2
-- | Adds a user to the contact list or edits an existing contact by their user identifier 
addContact ::
  Member TDLib r =>
  -- | The contact to add or edit; phone number can be empty and needs to be specified only if known, vCard is ignored
  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
  Bool ->
  Sem r (Error  Ok)
addContact :: Contact -> Bool -> Sem r (Error ∪ Ok)
addContact _1 :: Contact
_1 _2 :: Bool
_2 = AddContact -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddContact -> Sem r (Error ∪ Ok))
-> AddContact -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Contact -> Bool -> AddContact
AddContact Contact
_1 Bool
_2
-- | Adds new contacts or edits existing contacts by their phone numbers; contacts' user identifiers are ignored 
importContacts ::
  Member TDLib r =>
  -- | The list of contacts to import or edit; contacts' vCard are ignored and are not imported
  [Contact] ->
  Sem r (Error  ImportedContacts)
importContacts :: [Contact] -> Sem r (Error ∪ ImportedContacts)
importContacts _1 :: [Contact]
_1 = ImportContacts -> Sem r (Error ∪ ImportedContacts)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ImportContacts -> Sem r (Error ∪ ImportedContacts))
-> ImportContacts -> Sem r (Error ∪ ImportedContacts)
forall a b. (a -> b) -> a -> b
$ [Contact] -> ImportContacts
ImportContacts [Contact]
_1
-- | Returns all user contacts
getContacts ::
  Member TDLib r =>
  Sem r (Error  Users)
getContacts :: Sem r (Error ∪ Users)
getContacts  = GetContacts -> Sem r (Error ∪ Users)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetContacts -> Sem r (Error ∪ Users))
-> GetContacts -> Sem r (Error ∪ Users)
forall a b. (a -> b) -> a -> b
$ GetContacts
GetContacts 
-- | Searches for the specified query in the first names, last names and usernames of the known user contacts 
searchContacts ::
  Member TDLib r =>
  -- | Query to search for; may be empty to return all contacts 
  T ->
  -- | The maximum number of users to be returned
  I32 ->
  Sem r (Error  Users)
searchContacts :: T -> I32 -> Sem r (Error ∪ Users)
searchContacts _1 :: T
_1 _2 :: I32
_2 = SearchContacts -> Sem r (Error ∪ Users)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchContacts -> Sem r (Error ∪ Users))
-> SearchContacts -> Sem r (Error ∪ Users)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SearchContacts
SearchContacts T
_1 I32
_2
-- | Removes users from the contact list 
removeContacts ::
  Member TDLib r =>
  -- | Identifiers of users to be deleted
  [I32] ->
  Sem r (Error  Ok)
removeContacts :: [I32] -> Sem r (Error ∪ Ok)
removeContacts _1 :: [I32]
_1 = RemoveContacts -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveContacts -> Sem r (Error ∪ Ok))
-> RemoveContacts -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ [I32] -> RemoveContacts
RemoveContacts [I32]
_1
-- | Returns the total number of imported contacts
getImportedContactCount ::
  Member TDLib r =>
  Sem r (Error  Count)
getImportedContactCount :: Sem r (Error ∪ Count)
getImportedContactCount  = GetImportedContactCount -> Sem r (Error ∪ Count)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetImportedContactCount -> Sem r (Error ∪ Count))
-> GetImportedContactCount -> Sem r (Error ∪ Count)
forall a b. (a -> b) -> a -> b
$ GetImportedContactCount
GetImportedContactCount 
-- | 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 ::
  Member TDLib r =>
  [Contact] ->
  Sem r (Error  ImportedContacts)
changeImportedContacts :: [Contact] -> Sem r (Error ∪ ImportedContacts)
changeImportedContacts _1 :: [Contact]
_1 = ChangeImportedContacts -> Sem r (Error ∪ ImportedContacts)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ChangeImportedContacts -> Sem r (Error ∪ ImportedContacts))
-> ChangeImportedContacts -> Sem r (Error ∪ ImportedContacts)
forall a b. (a -> b) -> a -> b
$ [Contact] -> ChangeImportedContacts
ChangeImportedContacts [Contact]
_1
-- | Clears all imported contacts, contact list remains unchanged
clearImportedContacts ::
  Member TDLib r =>
  Sem r (Error  Ok)
clearImportedContacts :: Sem r (Error ∪ Ok)
clearImportedContacts  = ClearImportedContacts -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ClearImportedContacts -> Sem r (Error ∪ Ok))
-> ClearImportedContacts -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ClearImportedContacts
ClearImportedContacts 
-- | Shares the phone number of the current user with a mutual contact. Supposed to be called when the user clicks on chatActionBarSharePhoneNumber 
sharePhoneNumber ::
  Member TDLib r =>
  -- | Identifier of the user with whom to share the phone number. The user must be a mutual contact
  I32 ->
  Sem r (Error  Ok)
sharePhoneNumber :: I32 -> Sem r (Error ∪ Ok)
sharePhoneNumber _1 :: I32
_1 = SharePhoneNumber -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SharePhoneNumber -> Sem r (Error ∪ Ok))
-> SharePhoneNumber -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> SharePhoneNumber
SharePhoneNumber I32
_1
-- | Returns the profile photos of a user. The result of this query may be outdated: some photos might have been deleted already 
getUserProfilePhotos ::
  Member TDLib r =>
  -- | User identifier 
  I32 ->
  -- | The number of photos to skip; must be non-negative 
  I32 ->
  -- | The maximum number of photos to be returned; up to 100
  I32 ->
  Sem r (Error  UserProfilePhotos)
getUserProfilePhotos :: I32 -> I32 -> I32 -> Sem r (Error ∪ UserProfilePhotos)
getUserProfilePhotos _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 = GetUserProfilePhotos -> Sem r (Error ∪ UserProfilePhotos)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetUserProfilePhotos -> Sem r (Error ∪ UserProfilePhotos))
-> GetUserProfilePhotos -> Sem r (Error ∪ UserProfilePhotos)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> I32 -> GetUserProfilePhotos
GetUserProfilePhotos I32
_1 I32
_2 I32
_3
-- | 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 ::
  Member TDLib r =>
  -- | String representation of emoji. If empty, returns all known installed stickers 
  T ->
  -- | The maximum number of stickers to be returned
  I32 ->
  Sem r (Error  Stickers)
getStickers :: T -> I32 -> Sem r (Error ∪ Stickers)
getStickers _1 :: T
_1 _2 :: I32
_2 = GetStickers -> Sem r (Error ∪ Stickers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetStickers -> Sem r (Error ∪ Stickers))
-> GetStickers -> Sem r (Error ∪ Stickers)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> GetStickers
GetStickers T
_1 I32
_2
-- | Searches for stickers from public sticker sets that correspond to a given emoji 
searchStickers ::
  Member TDLib r =>
  -- | String representation of emoji; must be non-empty 
  T ->
  -- | The maximum number of stickers to be returned
  I32 ->
  Sem r (Error  Stickers)
searchStickers :: T -> I32 -> Sem r (Error ∪ Stickers)
searchStickers _1 :: T
_1 _2 :: I32
_2 = SearchStickers -> Sem r (Error ∪ Stickers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchStickers -> Sem r (Error ∪ Stickers))
-> SearchStickers -> Sem r (Error ∪ Stickers)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SearchStickers
SearchStickers T
_1 I32
_2
-- | Returns a list of installed sticker sets 
getInstalledStickerSets ::
  Member TDLib r =>
  -- | Pass true to return mask sticker sets; pass false to return ordinary sticker sets
  Bool ->
  Sem r (Error  StickerSets)
getInstalledStickerSets :: Bool -> Sem r (Error ∪ StickerSets)
getInstalledStickerSets _1 :: Bool
_1 = GetInstalledStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetInstalledStickerSets -> Sem r (Error ∪ StickerSets))
-> GetInstalledStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ Bool -> GetInstalledStickerSets
GetInstalledStickerSets Bool
_1
-- | Returns a list of archived sticker sets 
getArchivedStickerSets ::
  Member TDLib r =>
  -- | Pass true to return mask stickers sets; pass false to return ordinary sticker sets 
  Bool ->
  -- | Identifier of the sticker set from which to return the result 
  I64 ->
  -- | The maximum number of sticker sets to return
  I32 ->
  Sem r (Error  StickerSets)
getArchivedStickerSets :: Bool -> I64 -> I32 -> Sem r (Error ∪ StickerSets)
getArchivedStickerSets _1 :: Bool
_1 _2 :: I64
_2 _3 :: I32
_3 = GetArchivedStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetArchivedStickerSets -> Sem r (Error ∪ StickerSets))
-> GetArchivedStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ Bool -> I64 -> I32 -> GetArchivedStickerSets
GetArchivedStickerSets Bool
_1 I64
_2 I32
_3
-- | Returns a list of trending sticker sets. For the optimal performance the number of returned sticker sets is chosen by the library
getTrendingStickerSets ::
  Member TDLib r =>
  -- | The offset from which to return the sticker sets; must be non-negative
  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
  I32 ->
  Sem r (Error  StickerSets)
getTrendingStickerSets :: I32 -> I32 -> Sem r (Error ∪ StickerSets)
getTrendingStickerSets _1 :: I32
_1 _2 :: I32
_2 = GetTrendingStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetTrendingStickerSets -> Sem r (Error ∪ StickerSets))
-> GetTrendingStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetTrendingStickerSets
GetTrendingStickerSets I32
_1 I32
_2
-- | Returns a list of sticker sets attached to a file. Currently only photos and videos can have attached sticker sets 
getAttachedStickerSets ::
  Member TDLib r =>
  -- | File identifier
  I32 ->
  Sem r (Error  StickerSets)
getAttachedStickerSets :: I32 -> Sem r (Error ∪ StickerSets)
getAttachedStickerSets _1 :: I32
_1 = GetAttachedStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetAttachedStickerSets -> Sem r (Error ∪ StickerSets))
-> GetAttachedStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ I32 -> GetAttachedStickerSets
GetAttachedStickerSets I32
_1
-- | Returns information about a sticker set by its identifier 
getStickerSet ::
  Member TDLib r =>
  -- | Identifier of the sticker set
  I64 ->
  Sem r (Error  StickerSet)
getStickerSet :: I64 -> Sem r (Error ∪ StickerSet)
getStickerSet _1 :: I64
_1 = GetStickerSet -> Sem r (Error ∪ StickerSet)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetStickerSet -> Sem r (Error ∪ StickerSet))
-> GetStickerSet -> Sem r (Error ∪ StickerSet)
forall a b. (a -> b) -> a -> b
$ I64 -> GetStickerSet
GetStickerSet I64
_1
-- | Searches for a sticker set by its name 
searchStickerSet ::
  Member TDLib r =>
  -- | Name of the sticker set
  T ->
  Sem r (Error  StickerSet)
searchStickerSet :: T -> Sem r (Error ∪ StickerSet)
searchStickerSet _1 :: T
_1 = SearchStickerSet -> Sem r (Error ∪ StickerSet)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchStickerSet -> Sem r (Error ∪ StickerSet))
-> SearchStickerSet -> Sem r (Error ∪ StickerSet)
forall a b. (a -> b) -> a -> b
$ T -> SearchStickerSet
SearchStickerSet T
_1
-- | Searches for installed sticker sets by looking for specified query in their title and name 
searchInstalledStickerSets ::
  Member TDLib r =>
  -- | Pass true to return mask sticker sets; pass false to return ordinary sticker sets 
  Bool ->
  -- | Query to search for 
  T ->
  -- | The maximum number of sticker sets to return
  I32 ->
  Sem r (Error  StickerSets)
searchInstalledStickerSets :: Bool -> T -> I32 -> Sem r (Error ∪ StickerSets)
searchInstalledStickerSets _1 :: Bool
_1 _2 :: T
_2 _3 :: I32
_3 = SearchInstalledStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchInstalledStickerSets -> Sem r (Error ∪ StickerSets))
-> SearchInstalledStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ Bool -> T -> I32 -> SearchInstalledStickerSets
SearchInstalledStickerSets Bool
_1 T
_2 I32
_3
-- | Searches for ordinary sticker sets by looking for specified query in their title and name. Excludes installed sticker sets from the results 
searchStickerSets ::
  Member TDLib r =>
  -- | Query to search for
  T ->
  Sem r (Error  StickerSets)
searchStickerSets :: T -> Sem r (Error ∪ StickerSets)
searchStickerSets _1 :: T
_1 = SearchStickerSets -> Sem r (Error ∪ StickerSets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchStickerSets -> Sem r (Error ∪ StickerSets))
-> SearchStickerSets -> Sem r (Error ∪ StickerSets)
forall a b. (a -> b) -> a -> b
$ T -> SearchStickerSets
SearchStickerSets T
_1
-- | Installs/uninstalls or activates/archives a sticker set 
changeStickerSet ::
  Member TDLib r =>
  -- | Identifier of the sticker set 
  I64 ->
  -- | The new value of is_installed 
  Bool ->
  -- | The new value of is_archived. A sticker set can't be installed and archived simultaneously
  Bool ->
  Sem r (Error  Ok)
changeStickerSet :: I64 -> Bool -> Bool -> Sem r (Error ∪ Ok)
changeStickerSet _1 :: I64
_1 _2 :: Bool
_2 _3 :: Bool
_3 = ChangeStickerSet -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ChangeStickerSet -> Sem r (Error ∪ Ok))
-> ChangeStickerSet -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> Bool -> Bool -> ChangeStickerSet
ChangeStickerSet I64
_1 Bool
_2 Bool
_3
-- | Informs the server that some trending sticker sets have been viewed by the user 
viewTrendingStickerSets ::
  Member TDLib r =>
  -- | Identifiers of viewed trending sticker sets
  [I64] ->
  Sem r (Error  Ok)
viewTrendingStickerSets :: [I64] -> Sem r (Error ∪ Ok)
viewTrendingStickerSets _1 :: [I64]
_1 = ViewTrendingStickerSets -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ViewTrendingStickerSets -> Sem r (Error ∪ Ok))
-> ViewTrendingStickerSets -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ [I64] -> ViewTrendingStickerSets
ViewTrendingStickerSets [I64]
_1
-- | Changes the order of installed sticker sets 
reorderInstalledStickerSets ::
  Member TDLib r =>
  -- | Pass true to change the order of mask sticker sets; pass false to change the order of ordinary sticker sets 
  Bool ->
  -- | Identifiers of installed sticker sets in the new correct order
  [I64] ->
  Sem r (Error  Ok)
reorderInstalledStickerSets :: Bool -> [I64] -> Sem r (Error ∪ Ok)
reorderInstalledStickerSets _1 :: Bool
_1 _2 :: [I64]
_2 = ReorderInstalledStickerSets -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReorderInstalledStickerSets -> Sem r (Error ∪ Ok))
-> ReorderInstalledStickerSets -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Bool -> [I64] -> ReorderInstalledStickerSets
ReorderInstalledStickerSets Bool
_1 [I64]
_2
-- | Returns a list of recently used stickers 
getRecentStickers ::
  Member TDLib r =>
  -- | Pass true to return stickers and masks that were recently attached to photos or video files; pass false to return recently sent stickers
  Bool ->
  Sem r (Error  Stickers)
getRecentStickers :: Bool -> Sem r (Error ∪ Stickers)
getRecentStickers _1 :: Bool
_1 = GetRecentStickers -> Sem r (Error ∪ Stickers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRecentStickers -> Sem r (Error ∪ Stickers))
-> GetRecentStickers -> Sem r (Error ∪ Stickers)
forall a b. (a -> b) -> a -> b
$ Bool -> GetRecentStickers
GetRecentStickers Bool
_1
-- | 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 ::
  Member TDLib r =>
  -- | 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 
  Bool ->
  -- | Sticker file to add
  InputFile ->
  Sem r (Error  Stickers)
addRecentSticker :: Bool -> InputFile -> Sem r (Error ∪ Stickers)
addRecentSticker _1 :: Bool
_1 _2 :: InputFile
_2 = AddRecentSticker -> Sem r (Error ∪ Stickers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddRecentSticker -> Sem r (Error ∪ Stickers))
-> AddRecentSticker -> Sem r (Error ∪ Stickers)
forall a b. (a -> b) -> a -> b
$ Bool -> InputFile -> AddRecentSticker
AddRecentSticker Bool
_1 InputFile
_2
-- | Removes a sticker from the list of recently used stickers 
removeRecentSticker ::
  Member TDLib r =>
  -- | 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 
  Bool ->
  -- | Sticker file to delete
  InputFile ->
  Sem r (Error  Ok)
removeRecentSticker :: Bool -> InputFile -> Sem r (Error ∪ Ok)
removeRecentSticker _1 :: Bool
_1 _2 :: InputFile
_2 = RemoveRecentSticker -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveRecentSticker -> Sem r (Error ∪ Ok))
-> RemoveRecentSticker -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Bool -> InputFile -> RemoveRecentSticker
RemoveRecentSticker Bool
_1 InputFile
_2
-- | Clears the list of recently used stickers 
clearRecentStickers ::
  Member TDLib r =>
  -- | 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
  Bool ->
  Sem r (Error  Ok)
clearRecentStickers :: Bool -> Sem r (Error ∪ Ok)
clearRecentStickers _1 :: Bool
_1 = ClearRecentStickers -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ClearRecentStickers -> Sem r (Error ∪ Ok))
-> ClearRecentStickers -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Bool -> ClearRecentStickers
ClearRecentStickers Bool
_1
-- | Returns favorite stickers
getFavoriteStickers ::
  Member TDLib r =>
  Sem r (Error  Stickers)
getFavoriteStickers :: Sem r (Error ∪ Stickers)
getFavoriteStickers  = GetFavoriteStickers -> Sem r (Error ∪ Stickers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetFavoriteStickers -> Sem r (Error ∪ Stickers))
-> GetFavoriteStickers -> Sem r (Error ∪ Stickers)
forall a b. (a -> b) -> a -> b
$ GetFavoriteStickers
GetFavoriteStickers 
-- | 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 ::
  Member TDLib r =>
  -- | Sticker file to add
  InputFile ->
  Sem r (Error  Ok)
addFavoriteSticker :: InputFile -> Sem r (Error ∪ Ok)
addFavoriteSticker _1 :: InputFile
_1 = AddFavoriteSticker -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddFavoriteSticker -> Sem r (Error ∪ Ok))
-> AddFavoriteSticker -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> AddFavoriteSticker
AddFavoriteSticker InputFile
_1
-- | Removes a sticker from the list of favorite stickers 
removeFavoriteSticker ::
  Member TDLib r =>
  -- | Sticker file to delete from the list
  InputFile ->
  Sem r (Error  Ok)
removeFavoriteSticker :: InputFile -> Sem r (Error ∪ Ok)
removeFavoriteSticker _1 :: InputFile
_1 = RemoveFavoriteSticker -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveFavoriteSticker -> Sem r (Error ∪ Ok))
-> RemoveFavoriteSticker -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> RemoveFavoriteSticker
RemoveFavoriteSticker InputFile
_1
-- | 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 ::
  Member TDLib r =>
  -- | Sticker file identifier
  InputFile ->
  Sem r (Error  Emojis)
getStickerEmojis :: InputFile -> Sem r (Error ∪ Emojis)
getStickerEmojis _1 :: InputFile
_1 = GetStickerEmojis -> Sem r (Error ∪ Emojis)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetStickerEmojis -> Sem r (Error ∪ Emojis))
-> GetStickerEmojis -> Sem r (Error ∪ Emojis)
forall a b. (a -> b) -> a -> b
$ InputFile -> GetStickerEmojis
GetStickerEmojis InputFile
_1
-- | Searches for emojis by keywords. Supported only if the file database is enabled 
searchEmojis ::
  Member TDLib r =>
  -- | Text to search for 
  T ->
  -- | True, if only emojis, which exactly match text needs to be returned 
  Bool ->
  -- | List of possible IETF language tags of the user's input language; may be empty if unknown
  [T] ->
  Sem r (Error  Emojis)
searchEmojis :: T -> Bool -> [T] -> Sem r (Error ∪ Emojis)
searchEmojis _1 :: T
_1 _2 :: Bool
_2 _3 :: [T]
_3 = SearchEmojis -> Sem r (Error ∪ Emojis)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchEmojis -> Sem r (Error ∪ Emojis))
-> SearchEmojis -> Sem r (Error ∪ Emojis)
forall a b. (a -> b) -> a -> b
$ T -> Bool -> [T] -> SearchEmojis
SearchEmojis T
_1 Bool
_2 [T]
_3
-- | 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 ::
  Member TDLib r =>
  -- | Language code for which the emoji replacements will be suggested
  T ->
  Sem r (Error  HttpUrl)
getEmojiSuggestionsUrl :: T -> Sem r (Error ∪ HttpUrl)
getEmojiSuggestionsUrl _1 :: T
_1 = GetEmojiSuggestionsUrl -> Sem r (Error ∪ HttpUrl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetEmojiSuggestionsUrl -> Sem r (Error ∪ HttpUrl))
-> GetEmojiSuggestionsUrl -> Sem r (Error ∪ HttpUrl)
forall a b. (a -> b) -> a -> b
$ T -> GetEmojiSuggestionsUrl
GetEmojiSuggestionsUrl T
_1
-- | Returns saved animations
getSavedAnimations ::
  Member TDLib r =>
  Sem r (Error  Animations)
getSavedAnimations :: Sem r (Error ∪ Animations)
getSavedAnimations  = GetSavedAnimations -> Sem r (Error ∪ Animations)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSavedAnimations -> Sem r (Error ∪ Animations))
-> GetSavedAnimations -> Sem r (Error ∪ Animations)
forall a b. (a -> b) -> a -> b
$ GetSavedAnimations
GetSavedAnimations 
-- | 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 ::
  Member TDLib r =>
  -- | 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
  InputFile ->
  Sem r (Error  Ok)
addSavedAnimation :: InputFile -> Sem r (Error ∪ Ok)
addSavedAnimation _1 :: InputFile
_1 = AddSavedAnimation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddSavedAnimation -> Sem r (Error ∪ Ok))
-> AddSavedAnimation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> AddSavedAnimation
AddSavedAnimation InputFile
_1
-- | Removes an animation from the list of saved animations 
removeSavedAnimation ::
  Member TDLib r =>
  -- | Animation file to be removed
  InputFile ->
  Sem r (Error  Ok)
removeSavedAnimation :: InputFile -> Sem r (Error ∪ Ok)
removeSavedAnimation _1 :: InputFile
_1 = RemoveSavedAnimation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveSavedAnimation -> Sem r (Error ∪ Ok))
-> RemoveSavedAnimation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> RemoveSavedAnimation
RemoveSavedAnimation InputFile
_1
-- | Returns up to 20 recently used inline bots in the order of their last usage
getRecentInlineBots ::
  Member TDLib r =>
  Sem r (Error  Users)
getRecentInlineBots :: Sem r (Error ∪ Users)
getRecentInlineBots  = GetRecentInlineBots -> Sem r (Error ∪ Users)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRecentInlineBots -> Sem r (Error ∪ Users))
-> GetRecentInlineBots -> Sem r (Error ∪ Users)
forall a b. (a -> b) -> a -> b
$ GetRecentInlineBots
GetRecentInlineBots 
-- | Searches for recently used hashtags by their prefix 
searchHashtags ::
  Member TDLib r =>
  -- | Hashtag prefix to search for 
  T ->
  -- | The maximum number of hashtags to be returned
  I32 ->
  Sem r (Error  Hashtags)
searchHashtags :: T -> I32 -> Sem r (Error ∪ Hashtags)
searchHashtags _1 :: T
_1 _2 :: I32
_2 = SearchHashtags -> Sem r (Error ∪ Hashtags)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchHashtags -> Sem r (Error ∪ Hashtags))
-> SearchHashtags -> Sem r (Error ∪ Hashtags)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SearchHashtags
SearchHashtags T
_1 I32
_2
-- | Removes a hashtag from the list of recently used hashtags 
removeRecentHashtag ::
  Member TDLib r =>
  -- | Hashtag to delete
  T ->
  Sem r (Error  Ok)
removeRecentHashtag :: T -> Sem r (Error ∪ Ok)
removeRecentHashtag _1 :: T
_1 = RemoveRecentHashtag -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveRecentHashtag -> Sem r (Error ∪ Ok))
-> RemoveRecentHashtag -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> RemoveRecentHashtag
RemoveRecentHashtag T
_1
-- | 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 ::
  Member TDLib r =>
  -- | Message text with formatting
  FormattedText ->
  Sem r (Error  WebPage)
getWebPagePreview :: FormattedText -> Sem r (Error ∪ WebPage)
getWebPagePreview _1 :: FormattedText
_1 = GetWebPagePreview -> Sem r (Error ∪ WebPage)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetWebPagePreview -> Sem r (Error ∪ WebPage))
-> GetWebPagePreview -> Sem r (Error ∪ WebPage)
forall a b. (a -> b) -> a -> b
$ FormattedText -> GetWebPagePreview
GetWebPagePreview FormattedText
_1
-- | 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 ::
  Member TDLib r =>
  -- | The web page URL 
  T ->
  -- | If true, the full instant view for the web page will be returned
  Bool ->
  Sem r (Error  WebPageInstantView)
getWebPageInstantView :: T -> Bool -> Sem r (Error ∪ WebPageInstantView)
getWebPageInstantView _1 :: T
_1 _2 :: Bool
_2 = GetWebPageInstantView -> Sem r (Error ∪ WebPageInstantView)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetWebPageInstantView -> Sem r (Error ∪ WebPageInstantView))
-> GetWebPageInstantView -> Sem r (Error ∪ WebPageInstantView)
forall a b. (a -> b) -> a -> b
$ T -> Bool -> GetWebPageInstantView
GetWebPageInstantView T
_1 Bool
_2
-- | Uploads a new profile photo for the current user. If something changes, updateUser will be sent 
setProfilePhoto ::
  Member TDLib r =>
  -- | Profile photo to set. inputFileId and inputFileRemote may still be unsupported
  InputFile ->
  Sem r (Error  Ok)
setProfilePhoto :: InputFile -> Sem r (Error ∪ Ok)
setProfilePhoto _1 :: InputFile
_1 = SetProfilePhoto -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetProfilePhoto -> Sem r (Error ∪ Ok))
-> SetProfilePhoto -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> SetProfilePhoto
SetProfilePhoto InputFile
_1
-- | Deletes a profile photo. If something changes, updateUser will be sent 
deleteProfilePhoto ::
  Member TDLib r =>
  -- | Identifier of the profile photo to delete
  I64 ->
  Sem r (Error  Ok)
deleteProfilePhoto :: I64 -> Sem r (Error ∪ Ok)
deleteProfilePhoto _1 :: I64
_1 = DeleteProfilePhoto -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteProfilePhoto -> Sem r (Error ∪ Ok))
-> DeleteProfilePhoto -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> DeleteProfilePhoto
DeleteProfilePhoto I64
_1
-- | Changes the first and last name of the current user. If something changes, updateUser will be sent 
setName ::
  Member TDLib r =>
  -- | The new value of the first name for the user; 1-64 characters 
  T ->
  -- | The new value of the optional last name for the user; 0-64 characters
  T ->
  Sem r (Error  Ok)
setName :: T -> T -> Sem r (Error ∪ Ok)
setName _1 :: T
_1 _2 :: T
_2 = SetName -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetName -> Sem r (Error ∪ Ok)) -> SetName -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> T -> SetName
SetName T
_1 T
_2
-- | Changes the bio of the current user 
setBio ::
  Member TDLib r =>
  -- | The new value of the user bio; 0-70 characters without line feeds
  T ->
  Sem r (Error  Ok)
setBio :: T -> Sem r (Error ∪ Ok)
setBio _1 :: T
_1 = SetBio -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetBio -> Sem r (Error ∪ Ok)) -> SetBio -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> SetBio
SetBio T
_1
-- | Changes the username of the current user. If something changes, updateUser will be sent 
setUsername ::
  Member TDLib r =>
  -- | The new value of the username. Use an empty string to remove the username
  T ->
  Sem r (Error  Ok)
setUsername :: T -> Sem r (Error ∪ Ok)
setUsername _1 :: T
_1 = SetUsername -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetUsername -> Sem r (Error ∪ Ok))
-> SetUsername -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> SetUsername
SetUsername T
_1
-- | 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 ::
  Member TDLib r =>
  -- | The new location of the user
  Location ->
  Sem r (Error  Ok)
setLocation :: Location -> Sem r (Error ∪ Ok)
setLocation _1 :: Location
_1 = SetLocation -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetLocation -> Sem r (Error ∪ Ok))
-> SetLocation -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Location -> SetLocation
SetLocation Location
_1
-- | 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 ::
  Member TDLib r =>
  -- | The new phone number of the user in international format 
  T ->
  -- | Settings for the authentication of the user's phone number
  PhoneNumberAuthenticationSettings ->
  Sem r (Error  AuthenticationCodeInfo)
changePhoneNumber :: T
-> PhoneNumberAuthenticationSettings
-> Sem r (Error ∪ AuthenticationCodeInfo)
changePhoneNumber _1 :: T
_1 _2 :: PhoneNumberAuthenticationSettings
_2 = ChangePhoneNumber -> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ChangePhoneNumber -> Sem r (Error ∪ AuthenticationCodeInfo))
-> ChangePhoneNumber -> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ T -> PhoneNumberAuthenticationSettings -> ChangePhoneNumber
ChangePhoneNumber T
_1 PhoneNumberAuthenticationSettings
_2
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  AuthenticationCodeInfo)
resendChangePhoneNumberCode :: Sem r (Error ∪ AuthenticationCodeInfo)
resendChangePhoneNumberCode  = ResendChangePhoneNumberCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendChangePhoneNumberCode
 -> Sem r (Error ∪ AuthenticationCodeInfo))
-> ResendChangePhoneNumberCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ ResendChangePhoneNumberCode
ResendChangePhoneNumberCode 
-- | Checks the authentication code sent to confirm a new phone number of the user 
checkChangePhoneNumberCode ::
  Member TDLib r =>
  -- | Verification code received by SMS, phone call or flash call
  T ->
  Sem r (Error  Ok)
checkChangePhoneNumberCode :: T -> Sem r (Error ∪ Ok)
checkChangePhoneNumberCode _1 :: T
_1 = CheckChangePhoneNumberCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckChangePhoneNumberCode -> Sem r (Error ∪ Ok))
-> CheckChangePhoneNumberCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckChangePhoneNumberCode
CheckChangePhoneNumberCode T
_1
-- | Sets the list of commands supported by the bot; for bots only 
setCommands ::
  Member TDLib r =>
  -- | List of the bot's commands
  [BotCommand] ->
  Sem r (Error  Ok)
setCommands :: [BotCommand] -> Sem r (Error ∪ Ok)
setCommands _1 :: [BotCommand]
_1 = SetCommands -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetCommands -> Sem r (Error ∪ Ok))
-> SetCommands -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ [BotCommand] -> SetCommands
SetCommands [BotCommand]
_1
-- | Returns all active sessions of the current user
getActiveSessions ::
  Member TDLib r =>
  Sem r (Error  Sessions)
getActiveSessions :: Sem r (Error ∪ Sessions)
getActiveSessions  = GetActiveSessions -> Sem r (Error ∪ Sessions)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetActiveSessions -> Sem r (Error ∪ Sessions))
-> GetActiveSessions -> Sem r (Error ∪ Sessions)
forall a b. (a -> b) -> a -> b
$ GetActiveSessions
GetActiveSessions 
-- | Terminates a session of the current user 
terminateSession ::
  Member TDLib r =>
  -- | Session identifier
  I64 ->
  Sem r (Error  Ok)
terminateSession :: I64 -> Sem r (Error ∪ Ok)
terminateSession _1 :: I64
_1 = TerminateSession -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TerminateSession -> Sem r (Error ∪ Ok))
-> TerminateSession -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> TerminateSession
TerminateSession I64
_1
-- | Terminates all other sessions of the current user
terminateAllOtherSessions ::
  Member TDLib r =>
  Sem r (Error  Ok)
terminateAllOtherSessions :: Sem r (Error ∪ Ok)
terminateAllOtherSessions  = TerminateAllOtherSessions -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TerminateAllOtherSessions -> Sem r (Error ∪ Ok))
-> TerminateAllOtherSessions -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TerminateAllOtherSessions
TerminateAllOtherSessions 
-- | Returns all website where the current user used Telegram to log in
getConnectedWebsites ::
  Member TDLib r =>
  Sem r (Error  ConnectedWebsites)
getConnectedWebsites :: Sem r (Error ∪ ConnectedWebsites)
getConnectedWebsites  = GetConnectedWebsites -> Sem r (Error ∪ ConnectedWebsites)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetConnectedWebsites -> Sem r (Error ∪ ConnectedWebsites))
-> GetConnectedWebsites -> Sem r (Error ∪ ConnectedWebsites)
forall a b. (a -> b) -> a -> b
$ GetConnectedWebsites
GetConnectedWebsites 
-- | Disconnects website from the current user's Telegram account 
disconnectWebsite ::
  Member TDLib r =>
  -- | Website identifier
  I64 ->
  Sem r (Error  Ok)
disconnectWebsite :: I64 -> Sem r (Error ∪ Ok)
disconnectWebsite _1 :: I64
_1 = DisconnectWebsite -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DisconnectWebsite -> Sem r (Error ∪ Ok))
-> DisconnectWebsite -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> DisconnectWebsite
DisconnectWebsite I64
_1
-- | Disconnects all websites from the current user's Telegram account
disconnectAllWebsites ::
  Member TDLib r =>
  Sem r (Error  Ok)
disconnectAllWebsites :: Sem r (Error ∪ Ok)
disconnectAllWebsites  = DisconnectAllWebsites -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DisconnectAllWebsites -> Sem r (Error ∪ Ok))
-> DisconnectAllWebsites -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ DisconnectAllWebsites
DisconnectAllWebsites 
-- | Changes the username of a supergroup or channel, requires owner privileges in the supergroup or channel 
setSupergroupUsername ::
  Member TDLib r =>
  -- | Identifier of the supergroup or channel 
  I32 ->
  -- | New value of the username. Use an empty string to remove the username
  T ->
  Sem r (Error  Ok)
setSupergroupUsername :: I32 -> T -> Sem r (Error ∪ Ok)
setSupergroupUsername _1 :: I32
_1 _2 :: T
_2 = SetSupergroupUsername -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetSupergroupUsername -> Sem r (Error ∪ Ok))
-> SetSupergroupUsername -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SetSupergroupUsername
SetSupergroupUsername I32
_1 T
_2
-- | Changes the sticker set of a supergroup; requires can_change_info rights 
setSupergroupStickerSet ::
  Member TDLib r =>
  -- | Identifier of the supergroup 
  I32 ->
  -- | New value of the supergroup sticker set identifier. Use 0 to remove the supergroup sticker set
  I64 ->
  Sem r (Error  Ok)
setSupergroupStickerSet :: I32 -> I64 -> Sem r (Error ∪ Ok)
setSupergroupStickerSet _1 :: I32
_1 _2 :: I64
_2 = SetSupergroupStickerSet -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetSupergroupStickerSet -> Sem r (Error ∪ Ok))
-> SetSupergroupStickerSet -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I64 -> SetSupergroupStickerSet
SetSupergroupStickerSet I32
_1 I64
_2
-- | Toggles sender signatures messages sent in a channel; requires can_change_info rights 
toggleSupergroupSignMessages ::
  Member TDLib r =>
  -- | Identifier of the channel 
  I32 ->
  -- | New value of sign_messages
  Bool ->
  Sem r (Error  Ok)
toggleSupergroupSignMessages :: I32 -> Bool -> Sem r (Error ∪ Ok)
toggleSupergroupSignMessages _1 :: I32
_1 _2 :: Bool
_2 = ToggleSupergroupSignMessages -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ToggleSupergroupSignMessages -> Sem r (Error ∪ Ok))
-> ToggleSupergroupSignMessages -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> ToggleSupergroupSignMessages
ToggleSupergroupSignMessages I32
_1 Bool
_2
-- | Toggles whether the message history of a supergroup is available to new members; requires can_change_info rights 
toggleSupergroupIsAllHistoryAvailable ::
  Member TDLib r =>
  -- | The identifier of the supergroup 
  I32 ->
  -- | The new value of is_all_history_available
  Bool ->
  Sem r (Error  Ok)
toggleSupergroupIsAllHistoryAvailable :: I32 -> Bool -> Sem r (Error ∪ Ok)
toggleSupergroupIsAllHistoryAvailable _1 :: I32
_1 _2 :: Bool
_2 = ToggleSupergroupIsAllHistoryAvailable -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ToggleSupergroupIsAllHistoryAvailable -> Sem r (Error ∪ Ok))
-> ToggleSupergroupIsAllHistoryAvailable -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> ToggleSupergroupIsAllHistoryAvailable
ToggleSupergroupIsAllHistoryAvailable I32
_1 Bool
_2
-- | Reports some messages from a user in a supergroup as spam; requires administrator rights in the supergroup 
reportSupergroupSpam ::
  Member TDLib r =>
  -- | Supergroup identifier 
  I32 ->
  -- | User identifier 
  I32 ->
  -- | Identifiers of messages sent in the supergroup by the user. This list must be non-empty
  [I53] ->
  Sem r (Error  Ok)
reportSupergroupSpam :: I32 -> I32 -> [I32] -> Sem r (Error ∪ Ok)
reportSupergroupSpam _1 :: I32
_1 _2 :: I32
_2 _3 :: [I32]
_3 = ReportSupergroupSpam -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReportSupergroupSpam -> Sem r (Error ∪ Ok))
-> ReportSupergroupSpam -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> [I32] -> ReportSupergroupSpam
ReportSupergroupSpam I32
_1 I32
_2 [I32]
_3
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the supergroup or channel
  I32 ->
  -- | The type of users to return. By default, supergroupMembersRecent 
  SupergroupMembersFilter ->
  -- | Number of users to skip 
  I32 ->
  -- | The maximum number of users be returned; up to 200
  I32 ->
  Sem r (Error  ChatMembers)
getSupergroupMembers :: I32
-> SupergroupMembersFilter
-> I32
-> I32
-> Sem r (Error ∪ ChatMembers)
getSupergroupMembers _1 :: I32
_1 _2 :: SupergroupMembersFilter
_2 _3 :: I32
_3 _4 :: I32
_4 = GetSupergroupMembers -> Sem r (Error ∪ ChatMembers)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSupergroupMembers -> Sem r (Error ∪ ChatMembers))
-> GetSupergroupMembers -> Sem r (Error ∪ ChatMembers)
forall a b. (a -> b) -> a -> b
$ I32
-> SupergroupMembersFilter -> I32 -> I32 -> GetSupergroupMembers
GetSupergroupMembers I32
_1 SupergroupMembersFilter
_2 I32
_3 I32
_4
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the supergroup or channel
  I32 ->
  Sem r (Error  Ok)
deleteSupergroup :: I32 -> Sem r (Error ∪ Ok)
deleteSupergroup _1 :: I32
_1 = DeleteSupergroup -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteSupergroup -> Sem r (Error ∪ Ok))
-> DeleteSupergroup -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> DeleteSupergroup
DeleteSupergroup I32
_1
-- | Closes a secret chat, effectively transferring its state to secretChatStateClosed 
closeSecretChat ::
  Member TDLib r =>
  -- | Secret chat identifier
  I32 ->
  Sem r (Error  Ok)
closeSecretChat :: I32 -> Sem r (Error ∪ Ok)
closeSecretChat _1 :: I32
_1 = CloseSecretChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CloseSecretChat -> Sem r (Error ∪ Ok))
-> CloseSecretChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> CloseSecretChat
CloseSecretChat I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Search query by which to filter events 
  T ->
  -- | Identifier of an event from which to return results. Use 0 to get results from the latest events 
  I64 ->
  -- | The maximum number of events to return; up to 100
  I32 ->
  -- | The types of events to return. By default, all types will be returned 
  ChatEventLogFilters ->
  -- | User identifiers by which to filter events. By default, events relating to all users will be returned
  [I32] ->
  Sem r (Error  ChatEvents)
getChatEventLog :: I32
-> T
-> I64
-> I32
-> ChatEventLogFilters
-> [I32]
-> Sem r (Error ∪ ChatEvents)
getChatEventLog _1 :: I32
_1 _2 :: T
_2 _3 :: I64
_3 _4 :: I32
_4 _5 :: ChatEventLogFilters
_5 _6 :: [I32]
_6 = GetChatEventLog -> Sem r (Error ∪ ChatEvents)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatEventLog -> Sem r (Error ∪ ChatEvents))
-> GetChatEventLog -> Sem r (Error ∪ ChatEvents)
forall a b. (a -> b) -> a -> b
$ I32
-> T
-> I64
-> I32
-> ChatEventLogFilters
-> [I32]
-> GetChatEventLog
GetChatEventLog I32
_1 T
_2 I64
_3 I32
_4 ChatEventLogFilters
_5 [I32]
_6
-- | Returns an invoice payment form. This method should be called when the user presses inlineKeyboardButtonBuy 
getPaymentForm ::
  Member TDLib r =>
  -- | Chat identifier of the Invoice message 
  I53 ->
  -- | Message identifier
  I53 ->
  Sem r (Error  PaymentForm)
getPaymentForm :: I32 -> I32 -> Sem r (Error ∪ PaymentForm)
getPaymentForm _1 :: I32
_1 _2 :: I32
_2 = GetPaymentForm -> Sem r (Error ∪ PaymentForm)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPaymentForm -> Sem r (Error ∪ PaymentForm))
-> GetPaymentForm -> Sem r (Error ∪ PaymentForm)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetPaymentForm
GetPaymentForm I32
_1 I32
_2
-- | Validates the order information provided by a user and returns the available shipping options for a flexible invoice 
validateOrderInfo ::
  Member TDLib r =>
  -- | Chat identifier of the Invoice message 
  I53 ->
  -- | Message identifier 
  I53 ->
  -- | The order information, provided by the user 
  OrderInfo ->
  -- | True, if the order information can be saved
  Bool ->
  Sem r (Error  ValidatedOrderInfo)
validateOrderInfo :: I32
-> I32 -> OrderInfo -> Bool -> Sem r (Error ∪ ValidatedOrderInfo)
validateOrderInfo _1 :: I32
_1 _2 :: I32
_2 _3 :: OrderInfo
_3 _4 :: Bool
_4 = ValidateOrderInfo -> Sem r (Error ∪ ValidatedOrderInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ValidateOrderInfo -> Sem r (Error ∪ ValidatedOrderInfo))
-> ValidateOrderInfo -> Sem r (Error ∪ ValidatedOrderInfo)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> OrderInfo -> Bool -> ValidateOrderInfo
ValidateOrderInfo I32
_1 I32
_2 OrderInfo
_3 Bool
_4
-- | Sends a filled-out payment form to the bot for final verification 
sendPaymentForm ::
  Member TDLib r =>
  -- | Chat identifier of the Invoice message 
  I53 ->
  -- | Message identifier 
  I53 ->
  -- | Identifier returned by ValidateOrderInfo, or an empty string 
  T ->
  -- | Identifier of a chosen shipping option, if applicable
  T ->
  -- | The credentials chosen by user for payment
  InputCredentials ->
  Sem r (Error  PaymentResult)
sendPaymentForm :: I32
-> I32
-> T
-> T
-> InputCredentials
-> Sem r (Error ∪ PaymentResult)
sendPaymentForm _1 :: I32
_1 _2 :: I32
_2 _3 :: T
_3 _4 :: T
_4 _5 :: InputCredentials
_5 = SendPaymentForm -> Sem r (Error ∪ PaymentResult)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendPaymentForm -> Sem r (Error ∪ PaymentResult))
-> SendPaymentForm -> Sem r (Error ∪ PaymentResult)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> T -> T -> InputCredentials -> SendPaymentForm
SendPaymentForm I32
_1 I32
_2 T
_3 T
_4 InputCredentials
_5
-- | Returns information about a successful payment 
getPaymentReceipt ::
  Member TDLib r =>
  -- | Chat identifier of the PaymentSuccessful message 
  I53 ->
  -- | Message identifier
  I53 ->
  Sem r (Error  PaymentReceipt)
getPaymentReceipt :: I32 -> I32 -> Sem r (Error ∪ PaymentReceipt)
getPaymentReceipt _1 :: I32
_1 _2 :: I32
_2 = GetPaymentReceipt -> Sem r (Error ∪ PaymentReceipt)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPaymentReceipt -> Sem r (Error ∪ PaymentReceipt))
-> GetPaymentReceipt -> Sem r (Error ∪ PaymentReceipt)
forall a b. (a -> b) -> a -> b
$ I32 -> I32 -> GetPaymentReceipt
GetPaymentReceipt I32
_1 I32
_2
-- | Returns saved order info, if any
getSavedOrderInfo ::
  Member TDLib r =>
  Sem r (Error  OrderInfo)
getSavedOrderInfo :: Sem r (Error ∪ OrderInfo)
getSavedOrderInfo  = GetSavedOrderInfo -> Sem r (Error ∪ OrderInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSavedOrderInfo -> Sem r (Error ∪ OrderInfo))
-> GetSavedOrderInfo -> Sem r (Error ∪ OrderInfo)
forall a b. (a -> b) -> a -> b
$ GetSavedOrderInfo
GetSavedOrderInfo 
-- | Deletes saved order info
deleteSavedOrderInfo ::
  Member TDLib r =>
  Sem r (Error  Ok)
deleteSavedOrderInfo :: Sem r (Error ∪ Ok)
deleteSavedOrderInfo  = DeleteSavedOrderInfo -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteSavedOrderInfo -> Sem r (Error ∪ Ok))
-> DeleteSavedOrderInfo -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ DeleteSavedOrderInfo
DeleteSavedOrderInfo 
-- | Deletes saved credentials for all payment provider bots
deleteSavedCredentials ::
  Member TDLib r =>
  Sem r (Error  Ok)
deleteSavedCredentials :: Sem r (Error ∪ Ok)
deleteSavedCredentials  = DeleteSavedCredentials -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteSavedCredentials -> Sem r (Error ∪ Ok))
-> DeleteSavedCredentials -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ DeleteSavedCredentials
DeleteSavedCredentials 
-- | Returns a user that can be contacted to get support
getSupportUser ::
  Member TDLib r =>
  Sem r (Error  User)
getSupportUser :: Sem r (Error ∪ User)
getSupportUser  = GetSupportUser -> Sem r (Error ∪ User)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetSupportUser -> Sem r (Error ∪ User))
-> GetSupportUser -> Sem r (Error ∪ User)
forall a b. (a -> b) -> a -> b
$ GetSupportUser
GetSupportUser 
-- | Returns backgrounds installed by the user 
getBackgrounds ::
  Member TDLib r =>
  -- | True, if the backgrounds needs to be ordered for dark theme
  Bool ->
  Sem r (Error  Backgrounds)
getBackgrounds :: Bool -> Sem r (Error ∪ Backgrounds)
getBackgrounds _1 :: Bool
_1 = GetBackgrounds -> Sem r (Error ∪ Backgrounds)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBackgrounds -> Sem r (Error ∪ Backgrounds))
-> GetBackgrounds -> Sem r (Error ∪ Backgrounds)
forall a b. (a -> b) -> a -> b
$ Bool -> GetBackgrounds
GetBackgrounds Bool
_1
-- | Constructs a persistent HTTP URL for a background 
getBackgroundUrl ::
  Member TDLib r =>
  -- | Background name 
  T ->
  -- | Background type
  BackgroundType ->
  Sem r (Error  HttpUrl)
getBackgroundUrl :: T -> BackgroundType -> Sem r (Error ∪ HttpUrl)
getBackgroundUrl _1 :: T
_1 _2 :: BackgroundType
_2 = GetBackgroundUrl -> Sem r (Error ∪ HttpUrl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBackgroundUrl -> Sem r (Error ∪ HttpUrl))
-> GetBackgroundUrl -> Sem r (Error ∪ HttpUrl)
forall a b. (a -> b) -> a -> b
$ T -> BackgroundType -> GetBackgroundUrl
GetBackgroundUrl T
_1 BackgroundType
_2
-- | Searches for a background by its name 
searchBackground ::
  Member TDLib r =>
  -- | The name of the background
  T ->
  Sem r (Error  Background)
searchBackground :: T -> Sem r (Error ∪ Background)
searchBackground _1 :: T
_1 = SearchBackground -> Sem r (Error ∪ Background)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SearchBackground -> Sem r (Error ∪ Background))
-> SearchBackground -> Sem r (Error ∪ Background)
forall a b. (a -> b) -> a -> b
$ T -> SearchBackground
SearchBackground T
_1
-- | Changes the background selected by the user; adds background to the list of installed backgrounds
setBackground ::
  Member TDLib r =>
  -- | The input background to use, null for filled backgrounds
  InputBackground ->
  -- | Background type; null for default background. The method will return error 404 if type is null
  BackgroundType ->
  -- | True, if the background is chosen for dark theme
  Bool ->
  Sem r (Error  Background)
setBackground :: InputBackground
-> BackgroundType -> Bool -> Sem r (Error ∪ Background)
setBackground _1 :: InputBackground
_1 _2 :: BackgroundType
_2 _3 :: Bool
_3 = SetBackground -> Sem r (Error ∪ Background)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetBackground -> Sem r (Error ∪ Background))
-> SetBackground -> Sem r (Error ∪ Background)
forall a b. (a -> b) -> a -> b
$ InputBackground -> BackgroundType -> Bool -> SetBackground
SetBackground InputBackground
_1 BackgroundType
_2 Bool
_3
-- | Removes background from the list of installed backgrounds 
removeBackground ::
  Member TDLib r =>
  -- | The background identifier
  I64 ->
  Sem r (Error  Ok)
removeBackground :: I64 -> Sem r (Error ∪ Ok)
removeBackground _1 :: I64
_1 = RemoveBackground -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveBackground -> Sem r (Error ∪ Ok))
-> RemoveBackground -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> RemoveBackground
RemoveBackground I64
_1
-- | Resets list of installed backgrounds to its default value
resetBackgrounds ::
  Member TDLib r =>
  Sem r (Error  Ok)
resetBackgrounds :: Sem r (Error ∪ Ok)
resetBackgrounds  = ResetBackgrounds -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResetBackgrounds -> Sem r (Error ∪ Ok))
-> ResetBackgrounds -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ResetBackgrounds
ResetBackgrounds 
-- | Returns information about the current localization target. This is an offline request if only_local is true. Can be called before authorization 
getLocalizationTargetInfo ::
  Member TDLib r =>
  -- | If true, returns only locally available information without sending network requests
  Bool ->
  Sem r (Error  LocalizationTargetInfo)
getLocalizationTargetInfo :: Bool -> Sem r (Error ∪ LocalizationTargetInfo)
getLocalizationTargetInfo _1 :: Bool
_1 = GetLocalizationTargetInfo -> Sem r (Error ∪ LocalizationTargetInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLocalizationTargetInfo
 -> Sem r (Error ∪ LocalizationTargetInfo))
-> GetLocalizationTargetInfo
-> Sem r (Error ∪ LocalizationTargetInfo)
forall a b. (a -> b) -> a -> b
$ Bool -> GetLocalizationTargetInfo
GetLocalizationTargetInfo Bool
_1
-- | Returns information about a language pack. Returned language pack identifier may be different from a provided one. Can be called before authorization 
getLanguagePackInfo ::
  Member TDLib r =>
  -- | Language pack identifier
  T ->
  Sem r (Error  LanguagePackInfo)
getLanguagePackInfo :: T -> Sem r (Error ∪ LanguagePackInfo)
getLanguagePackInfo _1 :: T
_1 = GetLanguagePackInfo -> Sem r (Error ∪ LanguagePackInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLanguagePackInfo -> Sem r (Error ∪ LanguagePackInfo))
-> GetLanguagePackInfo -> Sem r (Error ∪ LanguagePackInfo)
forall a b. (a -> b) -> a -> b
$ T -> GetLanguagePackInfo
GetLanguagePackInfo T
_1
-- | Returns strings from a language pack in the current localization target by their keys. Can be called before authorization 
getLanguagePackStrings ::
  Member TDLib r =>
  -- | Language pack identifier of the strings to be returned 
  T ->
  -- | Language pack keys of the strings to be returned; leave empty to request all available strings
  [T] ->
  Sem r (Error  LanguagePackStrings)
getLanguagePackStrings :: T -> [T] -> Sem r (Error ∪ LanguagePackStrings)
getLanguagePackStrings _1 :: T
_1 _2 :: [T]
_2 = GetLanguagePackStrings -> Sem r (Error ∪ LanguagePackStrings)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLanguagePackStrings -> Sem r (Error ∪ LanguagePackStrings))
-> GetLanguagePackStrings -> Sem r (Error ∪ LanguagePackStrings)
forall a b. (a -> b) -> a -> b
$ T -> [T] -> GetLanguagePackStrings
GetLanguagePackStrings T
_1 [T]
_2
-- | 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 ::
  Member TDLib r =>
  -- | Language pack identifier
  T ->
  Sem r (Error  Ok)
synchronizeLanguagePack :: T -> Sem r (Error ∪ Ok)
synchronizeLanguagePack _1 :: T
_1 = SynchronizeLanguagePack -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SynchronizeLanguagePack -> Sem r (Error ∪ Ok))
-> SynchronizeLanguagePack -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> SynchronizeLanguagePack
SynchronizeLanguagePack T
_1
-- | Adds a custom server language pack to the list of installed language packs in current localization target. Can be called before authorization 
addCustomServerLanguagePack ::
  Member TDLib r =>
  -- | Identifier of a language pack to be added; may be different from a name that is used in an "https://t.me/setlanguage/" link
  T ->
  Sem r (Error  Ok)
addCustomServerLanguagePack :: T -> Sem r (Error ∪ Ok)
addCustomServerLanguagePack _1 :: T
_1 = AddCustomServerLanguagePack -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddCustomServerLanguagePack -> Sem r (Error ∪ Ok))
-> AddCustomServerLanguagePack -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> AddCustomServerLanguagePack
AddCustomServerLanguagePack T
_1
-- | Adds or changes a custom local language pack to the current localization target 
setCustomLanguagePack ::
  Member TDLib r =>
  -- | 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 
  LanguagePackInfo ->
  -- | Strings of the new language pack
  [LanguagePackString] ->
  Sem r (Error  Ok)
setCustomLanguagePack :: LanguagePackInfo -> [LanguagePackString] -> Sem r (Error ∪ Ok)
setCustomLanguagePack _1 :: LanguagePackInfo
_1 _2 :: [LanguagePackString]
_2 = SetCustomLanguagePack -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetCustomLanguagePack -> Sem r (Error ∪ Ok))
-> SetCustomLanguagePack -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ LanguagePackInfo -> [LanguagePackString] -> SetCustomLanguagePack
SetCustomLanguagePack LanguagePackInfo
_1 [LanguagePackString]
_2
-- | Edits information about a custom local language pack in the current localization target. Can be called before authorization 
editCustomLanguagePackInfo ::
  Member TDLib r =>
  -- | New information about the custom local language pack
  LanguagePackInfo ->
  Sem r (Error  Ok)
editCustomLanguagePackInfo :: LanguagePackInfo -> Sem r (Error ∪ Ok)
editCustomLanguagePackInfo _1 :: LanguagePackInfo
_1 = EditCustomLanguagePackInfo -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditCustomLanguagePackInfo -> Sem r (Error ∪ Ok))
-> EditCustomLanguagePackInfo -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ LanguagePackInfo -> EditCustomLanguagePackInfo
EditCustomLanguagePackInfo LanguagePackInfo
_1
-- | Adds, edits or deletes a string in a custom local language pack. Can be called before authorization 
setCustomLanguagePackString ::
  Member TDLib r =>
  -- | Identifier of a previously added custom local language pack in the current localization target 
  T ->
  -- | New language pack string
  LanguagePackString ->
  Sem r (Error  Ok)
setCustomLanguagePackString :: T -> LanguagePackString -> Sem r (Error ∪ Ok)
setCustomLanguagePackString _1 :: T
_1 _2 :: LanguagePackString
_2 = SetCustomLanguagePackString -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetCustomLanguagePackString -> Sem r (Error ∪ Ok))
-> SetCustomLanguagePackString -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> LanguagePackString -> SetCustomLanguagePackString
SetCustomLanguagePackString T
_1 LanguagePackString
_2
-- | 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 ::
  Member TDLib r =>
  -- | Identifier of the language pack to delete
  T ->
  Sem r (Error  Ok)
deleteLanguagePack :: T -> Sem r (Error ∪ Ok)
deleteLanguagePack _1 :: T
_1 = DeleteLanguagePack -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteLanguagePack -> Sem r (Error ∪ Ok))
-> DeleteLanguagePack -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> DeleteLanguagePack
DeleteLanguagePack T
_1
-- | Registers the currently used device for receiving push notifications. Returns a globally unique identifier of the push notification subscription 
registerDevice ::
  Member TDLib r =>
  -- | Device token 
  DeviceToken ->
  -- | List of user identifiers of other users currently using the client
  [I32] ->
  Sem r (Error  PushReceiverId)
registerDevice :: DeviceToken -> [I32] -> Sem r (Error ∪ PushReceiverId)
registerDevice _1 :: DeviceToken
_1 _2 :: [I32]
_2 = RegisterDevice -> Sem r (Error ∪ PushReceiverId)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RegisterDevice -> Sem r (Error ∪ PushReceiverId))
-> RegisterDevice -> Sem r (Error ∪ PushReceiverId)
forall a b. (a -> b) -> a -> b
$ DeviceToken -> [I32] -> RegisterDevice
RegisterDevice DeviceToken
_1 [I32]
_2
-- | 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 ::
  Member TDLib r =>
  -- | JSON-encoded push notification payload with all fields sent by the server, and "google.sent_time" and "google.notification.sound" fields added
  T ->
  Sem r (Error  Ok)
processPushNotification :: T -> Sem r (Error ∪ Ok)
processPushNotification _1 :: T
_1 = ProcessPushNotification -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ProcessPushNotification -> Sem r (Error ∪ Ok))
-> ProcessPushNotification -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> ProcessPushNotification
ProcessPushNotification T
_1
-- | 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 ::
  Member TDLib r =>
  -- | JSON-encoded push notification payload
  T ->
  Sem r (Error  PushReceiverId)
getPushReceiverId :: T -> Sem r (Error ∪ PushReceiverId)
getPushReceiverId _1 :: T
_1 = GetPushReceiverId -> Sem r (Error ∪ PushReceiverId)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPushReceiverId -> Sem r (Error ∪ PushReceiverId))
-> GetPushReceiverId -> Sem r (Error ∪ PushReceiverId)
forall a b. (a -> b) -> a -> b
$ T -> GetPushReceiverId
GetPushReceiverId T
_1
-- | Returns t.me URLs recently visited by a newly registered user 
getRecentlyVisitedTMeUrls ::
  Member TDLib r =>
  -- | Google Play referrer to identify the user
  T ->
  Sem r (Error  TMeUrls)
getRecentlyVisitedTMeUrls :: T -> Sem r (Error ∪ TMeUrls)
getRecentlyVisitedTMeUrls _1 :: T
_1 = GetRecentlyVisitedTMeUrls -> Sem r (Error ∪ TMeUrls)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetRecentlyVisitedTMeUrls -> Sem r (Error ∪ TMeUrls))
-> GetRecentlyVisitedTMeUrls -> Sem r (Error ∪ TMeUrls)
forall a b. (a -> b) -> a -> b
$ T -> GetRecentlyVisitedTMeUrls
GetRecentlyVisitedTMeUrls T
_1
-- | Changes user privacy settings 
setUserPrivacySettingRules ::
  Member TDLib r =>
  -- | The privacy setting 
  UserPrivacySetting ->
  -- | The new privacy rules
  UserPrivacySettingRules ->
  Sem r (Error  Ok)
setUserPrivacySettingRules :: UserPrivacySetting -> UserPrivacySettingRules -> Sem r (Error ∪ Ok)
setUserPrivacySettingRules _1 :: UserPrivacySetting
_1 _2 :: UserPrivacySettingRules
_2 = SetUserPrivacySettingRules -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetUserPrivacySettingRules -> Sem r (Error ∪ Ok))
-> SetUserPrivacySettingRules -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ UserPrivacySetting
-> UserPrivacySettingRules -> SetUserPrivacySettingRules
SetUserPrivacySettingRules UserPrivacySetting
_1 UserPrivacySettingRules
_2
-- | Returns the current privacy settings 
getUserPrivacySettingRules ::
  Member TDLib r =>
  -- | The privacy setting
  UserPrivacySetting ->
  Sem r (Error  UserPrivacySettingRules)
getUserPrivacySettingRules :: UserPrivacySetting -> Sem r (Error ∪ UserPrivacySettingRules)
getUserPrivacySettingRules _1 :: UserPrivacySetting
_1 = GetUserPrivacySettingRules
-> Sem r (Error ∪ UserPrivacySettingRules)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetUserPrivacySettingRules
 -> Sem r (Error ∪ UserPrivacySettingRules))
-> GetUserPrivacySettingRules
-> Sem r (Error ∪ UserPrivacySettingRules)
forall a b. (a -> b) -> a -> b
$ UserPrivacySetting -> GetUserPrivacySettingRules
GetUserPrivacySettingRules UserPrivacySetting
_1
-- | 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 ::
  Member TDLib r =>
  -- | The name of the option
  T ->
  Sem r (Error  OptionValue)
getOption :: T -> Sem r (Error ∪ OptionValue)
getOption _1 :: T
_1 = GetOption -> Sem r (Error ∪ OptionValue)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetOption -> Sem r (Error ∪ OptionValue))
-> GetOption -> Sem r (Error ∪ OptionValue)
forall a b. (a -> b) -> a -> b
$ T -> GetOption
GetOption T
_1
-- | 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 ::
  Member TDLib r =>
  -- | The name of the option 
  T ->
  -- | The new value of the option
  OptionValue ->
  Sem r (Error  Ok)
setOption :: T -> OptionValue -> Sem r (Error ∪ Ok)
setOption _1 :: T
_1 _2 :: OptionValue
_2 = SetOption -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetOption -> Sem r (Error ∪ Ok))
-> SetOption -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> OptionValue -> SetOption
SetOption T
_1 OptionValue
_2
-- | Changes the period of inactivity after which the account of the current user will automatically be deleted 
setAccountTtl ::
  Member TDLib r =>
  -- | New account TTL
  AccountTtl ->
  Sem r (Error  Ok)
setAccountTtl :: AccountTtl -> Sem r (Error ∪ Ok)
setAccountTtl _1 :: AccountTtl
_1 = SetAccountTtl -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetAccountTtl -> Sem r (Error ∪ Ok))
-> SetAccountTtl -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ AccountTtl -> SetAccountTtl
SetAccountTtl AccountTtl
_1
-- | Returns the period of inactivity after which the account of the current user will automatically be deleted
getAccountTtl ::
  Member TDLib r =>
  Sem r (Error  AccountTtl)
getAccountTtl :: Sem r (Error ∪ AccountTtl)
getAccountTtl  = GetAccountTtl -> Sem r (Error ∪ AccountTtl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetAccountTtl -> Sem r (Error ∪ AccountTtl))
-> GetAccountTtl -> Sem r (Error ∪ AccountTtl)
forall a b. (a -> b) -> a -> b
$ GetAccountTtl
GetAccountTtl 
-- | 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 ::
  Member TDLib r =>
  -- | The reason why the account was deleted; optional
  T ->
  Sem r (Error  Ok)
deleteAccount :: T -> Sem r (Error ∪ Ok)
deleteAccount _1 :: T
_1 = DeleteAccount -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeleteAccount -> Sem r (Error ∪ Ok))
-> DeleteAccount -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> DeleteAccount
DeleteAccount T
_1
-- | Removes a chat action bar without any other action 
removeChatActionBar ::
  Member TDLib r =>
  -- | Chat identifier
  I53 ->
  Sem r (Error  Ok)
removeChatActionBar :: I32 -> Sem r (Error ∪ Ok)
removeChatActionBar _1 :: I32
_1 = RemoveChatActionBar -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveChatActionBar -> Sem r (Error ∪ Ok))
-> RemoveChatActionBar -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> RemoveChatActionBar
RemoveChatActionBar I32
_1
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The reason for reporting the chat 
  ChatReportReason ->
  -- | Identifiers of reported messages, if any
  [I53] ->
  Sem r (Error  Ok)
reportChat :: I32 -> ChatReportReason -> [I32] -> Sem r (Error ∪ Ok)
reportChat _1 :: I32
_1 _2 :: ChatReportReason
_2 _3 :: [I32]
_3 = ReportChat -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ReportChat -> Sem r (Error ∪ Ok))
-> ReportChat -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> ChatReportReason -> [I32] -> ReportChat
ReportChat I32
_1 ChatReportReason
_2 [I32]
_3
-- | 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 ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Parameters from "tg://statsrefresh?params=******" link 
  T ->
  -- | Pass true if a URL with the dark theme must be returned
  Bool ->
  Sem r (Error  HttpUrl)
getChatStatisticsUrl :: I32 -> T -> Bool -> Sem r (Error ∪ HttpUrl)
getChatStatisticsUrl _1 :: I32
_1 _2 :: T
_2 _3 :: Bool
_3 = GetChatStatisticsUrl -> Sem r (Error ∪ HttpUrl)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatStatisticsUrl -> Sem r (Error ∪ HttpUrl))
-> GetChatStatisticsUrl -> Sem r (Error ∪ HttpUrl)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> Bool -> GetChatStatisticsUrl
GetChatStatisticsUrl I32
_1 T
_2 Bool
_3
-- | Returns detailed statistics about a chat. Currently this method can be used only for channels. Requires administrator rights in the channel 
getChatStatistics ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | Pass true if a dark theme is used by the app
  Bool ->
  Sem r (Error  ChatStatistics)
getChatStatistics :: I32 -> Bool -> Sem r (Error ∪ ChatStatistics)
getChatStatistics _1 :: I32
_1 _2 :: Bool
_2 = GetChatStatistics -> Sem r (Error ∪ ChatStatistics)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatStatistics -> Sem r (Error ∪ ChatStatistics))
-> GetChatStatistics -> Sem r (Error ∪ ChatStatistics)
forall a b. (a -> b) -> a -> b
$ I32 -> Bool -> GetChatStatistics
GetChatStatistics I32
_1 Bool
_2
-- | Loads asynchronous or zoomed in chat statistics graph 
getChatStatisticsGraph ::
  Member TDLib r =>
  -- | Chat identifier 
  I53 ->
  -- | The token for graph loading 
  T ->
  -- | X-value for zoomed in graph or 0 otherwise
  I53 ->
  Sem r (Error  StatisticsGraph)
getChatStatisticsGraph :: I32 -> T -> I32 -> Sem r (Error ∪ StatisticsGraph)
getChatStatisticsGraph _1 :: I32
_1 _2 :: T
_2 _3 :: I32
_3 = GetChatStatisticsGraph -> Sem r (Error ∪ StatisticsGraph)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetChatStatisticsGraph -> Sem r (Error ∪ StatisticsGraph))
-> GetChatStatisticsGraph -> Sem r (Error ∪ StatisticsGraph)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> I32 -> GetChatStatisticsGraph
GetChatStatisticsGraph I32
_1 T
_2 I32
_3
-- | Returns storage usage statistics. Can be called before authorization 
getStorageStatistics ::
  Member TDLib r =>
  -- | 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
  I32 ->
  Sem r (Error  StorageStatistics)
getStorageStatistics :: I32 -> Sem r (Error ∪ StorageStatistics)
getStorageStatistics _1 :: I32
_1 = GetStorageStatistics -> Sem r (Error ∪ StorageStatistics)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetStorageStatistics -> Sem r (Error ∪ StorageStatistics))
-> GetStorageStatistics -> Sem r (Error ∪ StorageStatistics)
forall a b. (a -> b) -> a -> b
$ I32 -> GetStorageStatistics
GetStorageStatistics I32
_1
-- | Quickly returns approximate storage usage statistics. Can be called before authorization
getStorageStatisticsFast ::
  Member TDLib r =>
  Sem r (Error  StorageStatisticsFast)
getStorageStatisticsFast :: Sem r (Error ∪ StorageStatisticsFast)
getStorageStatisticsFast  = GetStorageStatisticsFast -> Sem r (Error ∪ StorageStatisticsFast)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetStorageStatisticsFast -> Sem r (Error ∪ StorageStatisticsFast))
-> GetStorageStatisticsFast
-> Sem r (Error ∪ StorageStatisticsFast)
forall a b. (a -> b) -> a -> b
$ GetStorageStatisticsFast
GetStorageStatisticsFast 
-- | Returns database statistics
getDatabaseStatistics ::
  Member TDLib r =>
  Sem r (Error  DatabaseStatistics)
getDatabaseStatistics :: Sem r (Error ∪ DatabaseStatistics)
getDatabaseStatistics  = GetDatabaseStatistics -> Sem r (Error ∪ DatabaseStatistics)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetDatabaseStatistics -> Sem r (Error ∪ DatabaseStatistics))
-> GetDatabaseStatistics -> Sem r (Error ∪ DatabaseStatistics)
forall a b. (a -> b) -> a -> b
$ GetDatabaseStatistics
GetDatabaseStatistics 
-- | Optimizes storage usage, i.e. deletes some files and returns new storage usage statistics. Secret thumbnails can't be deleted
optimizeStorage ::
  Member TDLib r =>
  -- | Limit on the total size of files after deletion. Pass -1 to use the default limit
  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
  I32 ->
  -- | Limit on the total count of files after deletion. Pass -1 to use the default limit
  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
  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
  [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)
  [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)
  [I53] ->
  -- | Pass true if deleted file statistics needs to be returned instead of the whole storage usage statistics. Affects only returned statistics
  Bool ->
  -- | Same as in getStorageStatistics. Affects only returned statistics
  I32 ->
  Sem r (Error  StorageStatistics)
optimizeStorage :: I32
-> I32
-> I32
-> I32
-> [FileType]
-> [I32]
-> [I32]
-> Bool
-> I32
-> Sem r (Error ∪ StorageStatistics)
optimizeStorage _1 :: I32
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: [FileType]
_5 _6 :: [I32]
_6 _7 :: [I32]
_7 _8 :: Bool
_8 _9 :: I32
_9 = OptimizeStorage -> Sem r (Error ∪ StorageStatistics)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (OptimizeStorage -> Sem r (Error ∪ StorageStatistics))
-> OptimizeStorage -> Sem r (Error ∪ StorageStatistics)
forall a b. (a -> b) -> a -> b
$ I32
-> I32
-> I32
-> I32
-> [FileType]
-> [I32]
-> [I32]
-> Bool
-> I32
-> OptimizeStorage
OptimizeStorage I32
_1 I32
_2 I32
_3 I32
_4 [FileType]
_5 [I32]
_6 [I32]
_7 Bool
_8 I32
_9
-- | 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 ::
  Member TDLib r =>
  NetworkType ->
  Sem r (Error  Ok)
setNetworkType :: NetworkType -> Sem r (Error ∪ Ok)
setNetworkType _1 :: NetworkType
_1 = SetNetworkType -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetNetworkType -> Sem r (Error ∪ Ok))
-> SetNetworkType -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ NetworkType -> SetNetworkType
SetNetworkType NetworkType
_1
-- | Returns network data usage statistics. Can be called before authorization 
getNetworkStatistics ::
  Member TDLib r =>
  -- | If true, returns only data for the current library launch
  Bool ->
  Sem r (Error  NetworkStatistics)
getNetworkStatistics :: Bool -> Sem r (Error ∪ NetworkStatistics)
getNetworkStatistics _1 :: Bool
_1 = GetNetworkStatistics -> Sem r (Error ∪ NetworkStatistics)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetNetworkStatistics -> Sem r (Error ∪ NetworkStatistics))
-> GetNetworkStatistics -> Sem r (Error ∪ NetworkStatistics)
forall a b. (a -> b) -> a -> b
$ Bool -> GetNetworkStatistics
GetNetworkStatistics Bool
_1
-- | Adds the specified data to data usage statistics. Can be called before authorization 
addNetworkStatistics ::
  Member TDLib r =>
  -- | The network statistics entry with the data to be added to statistics
  NetworkStatisticsEntry ->
  Sem r (Error  Ok)
addNetworkStatistics :: NetworkStatisticsEntry -> Sem r (Error ∪ Ok)
addNetworkStatistics _1 :: NetworkStatisticsEntry
_1 = AddNetworkStatistics -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddNetworkStatistics -> Sem r (Error ∪ Ok))
-> AddNetworkStatistics -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ NetworkStatisticsEntry -> AddNetworkStatistics
AddNetworkStatistics NetworkStatisticsEntry
_1
-- | Resets all network data usage statistics to zero. Can be called before authorization
resetNetworkStatistics ::
  Member TDLib r =>
  Sem r (Error  Ok)
resetNetworkStatistics :: Sem r (Error ∪ Ok)
resetNetworkStatistics  = ResetNetworkStatistics -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResetNetworkStatistics -> Sem r (Error ∪ Ok))
-> ResetNetworkStatistics -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ ResetNetworkStatistics
ResetNetworkStatistics 
-- | Returns auto-download settings presets for the current user
getAutoDownloadSettingsPresets ::
  Member TDLib r =>
  Sem r (Error  AutoDownloadSettingsPresets)
getAutoDownloadSettingsPresets :: Sem r (Error ∪ AutoDownloadSettingsPresets)
getAutoDownloadSettingsPresets  = GetAutoDownloadSettingsPresets
-> Sem r (Error ∪ AutoDownloadSettingsPresets)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetAutoDownloadSettingsPresets
 -> Sem r (Error ∪ AutoDownloadSettingsPresets))
-> GetAutoDownloadSettingsPresets
-> Sem r (Error ∪ AutoDownloadSettingsPresets)
forall a b. (a -> b) -> a -> b
$ GetAutoDownloadSettingsPresets
GetAutoDownloadSettingsPresets 
-- | Sets auto-download settings 
setAutoDownloadSettings ::
  Member TDLib r =>
  -- | New user auto-download settings 
  AutoDownloadSettings ->
  -- | Type of the network for which the new settings are applied
  NetworkType ->
  Sem r (Error  Ok)
setAutoDownloadSettings :: AutoDownloadSettings -> NetworkType -> Sem r (Error ∪ Ok)
setAutoDownloadSettings _1 :: AutoDownloadSettings
_1 _2 :: NetworkType
_2 = SetAutoDownloadSettings -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetAutoDownloadSettings -> Sem r (Error ∪ Ok))
-> SetAutoDownloadSettings -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ AutoDownloadSettings -> NetworkType -> SetAutoDownloadSettings
SetAutoDownloadSettings AutoDownloadSettings
_1 NetworkType
_2
-- | Returns information about a bank card 
getBankCardInfo ::
  Member TDLib r =>
  -- | The bank card number
  T ->
  Sem r (Error  BankCardInfo)
getBankCardInfo :: T -> Sem r (Error ∪ BankCardInfo)
getBankCardInfo _1 :: T
_1 = GetBankCardInfo -> Sem r (Error ∪ BankCardInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetBankCardInfo -> Sem r (Error ∪ BankCardInfo))
-> GetBankCardInfo -> Sem r (Error ∪ BankCardInfo)
forall a b. (a -> b) -> a -> b
$ T -> GetBankCardInfo
GetBankCardInfo T
_1
-- | Returns one of the available Telegram Passport elements 
getPassportElement ::
  Member TDLib r =>
  -- | Telegram Passport element type 
  PassportElementType ->
  -- | Password of the current user
  T ->
  Sem r (Error  PassportElement)
getPassportElement :: PassportElementType -> T -> Sem r (Error ∪ PassportElement)
getPassportElement _1 :: PassportElementType
_1 _2 :: T
_2 = GetPassportElement -> Sem r (Error ∪ PassportElement)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPassportElement -> Sem r (Error ∪ PassportElement))
-> GetPassportElement -> Sem r (Error ∪ PassportElement)
forall a b. (a -> b) -> a -> b
$ PassportElementType -> T -> GetPassportElement
GetPassportElement PassportElementType
_1 T
_2
-- | Returns all available Telegram Passport elements 
getAllPassportElements ::
  Member TDLib r =>
  -- | Password of the current user
  T ->
  Sem r (Error  PassportElements)
getAllPassportElements :: T -> Sem r (Error ∪ PassportElements)
getAllPassportElements _1 :: T
_1 = GetAllPassportElements -> Sem r (Error ∪ PassportElements)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetAllPassportElements -> Sem r (Error ∪ PassportElements))
-> GetAllPassportElements -> Sem r (Error ∪ PassportElements)
forall a b. (a -> b) -> a -> b
$ T -> GetAllPassportElements
GetAllPassportElements T
_1
-- | 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 ::
  Member TDLib r =>
  -- | Input Telegram Passport element 
  InputPassportElement ->
  -- | Password of the current user
  T ->
  Sem r (Error  PassportElement)
setPassportElement :: InputPassportElement -> T -> Sem r (Error ∪ PassportElement)
setPassportElement _1 :: InputPassportElement
_1 _2 :: T
_2 = SetPassportElement -> Sem r (Error ∪ PassportElement)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetPassportElement -> Sem r (Error ∪ PassportElement))
-> SetPassportElement -> Sem r (Error ∪ PassportElement)
forall a b. (a -> b) -> a -> b
$ InputPassportElement -> T -> SetPassportElement
SetPassportElement InputPassportElement
_1 T
_2
-- | Deletes a Telegram Passport element 
deletePassportElement ::
  Member TDLib r =>
  -- | Element type
  PassportElementType ->
  Sem r (Error  Ok)
deletePassportElement :: PassportElementType -> Sem r (Error ∪ Ok)
deletePassportElement _1 :: PassportElementType
_1 = DeletePassportElement -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DeletePassportElement -> Sem r (Error ∪ Ok))
-> DeletePassportElement -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ PassportElementType -> DeletePassportElement
DeletePassportElement PassportElementType
_1
-- | 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 ::
  Member TDLib r =>
  -- | User identifier 
  I32 ->
  -- | The errors
  [InputPassportElementError] ->
  Sem r (Error  Ok)
setPassportElementErrors :: I32 -> [InputPassportElementError] -> Sem r (Error ∪ Ok)
setPassportElementErrors _1 :: I32
_1 _2 :: [InputPassportElementError]
_2 = SetPassportElementErrors -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetPassportElementErrors -> Sem r (Error ∪ Ok))
-> SetPassportElementErrors -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> [InputPassportElementError] -> SetPassportElementErrors
SetPassportElementErrors I32
_1 [InputPassportElementError]
_2
-- | 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 ::
  Member TDLib r =>
  -- | A two-letter ISO 3166-1 alpha-2 country code
  T ->
  Sem r (Error  Text)
getPreferredCountryLanguage :: T -> Sem r (Error ∪ Text)
getPreferredCountryLanguage _1 :: T
_1 = GetPreferredCountryLanguage -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPreferredCountryLanguage -> Sem r (Error ∪ Text))
-> GetPreferredCountryLanguage -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ T -> GetPreferredCountryLanguage
GetPreferredCountryLanguage T
_1
-- | Sends a code to verify a phone number to be added to a user's Telegram Passport
sendPhoneNumberVerificationCode ::
  Member TDLib r =>
  -- | The phone number of the user, in international format 
  T ->
  -- | Settings for the authentication of the user's phone number
  PhoneNumberAuthenticationSettings ->
  Sem r (Error  AuthenticationCodeInfo)
sendPhoneNumberVerificationCode :: T
-> PhoneNumberAuthenticationSettings
-> Sem r (Error ∪ AuthenticationCodeInfo)
sendPhoneNumberVerificationCode _1 :: T
_1 _2 :: PhoneNumberAuthenticationSettings
_2 = SendPhoneNumberVerificationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendPhoneNumberVerificationCode
 -> Sem r (Error ∪ AuthenticationCodeInfo))
-> SendPhoneNumberVerificationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ T
-> PhoneNumberAuthenticationSettings
-> SendPhoneNumberVerificationCode
SendPhoneNumberVerificationCode T
_1 PhoneNumberAuthenticationSettings
_2
-- | Re-sends the code to verify a phone number to be added to a user's Telegram Passport
resendPhoneNumberVerificationCode ::
  Member TDLib r =>
  Sem r (Error  AuthenticationCodeInfo)
resendPhoneNumberVerificationCode :: Sem r (Error ∪ AuthenticationCodeInfo)
resendPhoneNumberVerificationCode  = ResendPhoneNumberVerificationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendPhoneNumberVerificationCode
 -> Sem r (Error ∪ AuthenticationCodeInfo))
-> ResendPhoneNumberVerificationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ ResendPhoneNumberVerificationCode
ResendPhoneNumberVerificationCode 
-- | Checks the phone number verification code for Telegram Passport 
checkPhoneNumberVerificationCode ::
  Member TDLib r =>
  -- | Verification code
  T ->
  Sem r (Error  Ok)
checkPhoneNumberVerificationCode :: T -> Sem r (Error ∪ Ok)
checkPhoneNumberVerificationCode _1 :: T
_1 = CheckPhoneNumberVerificationCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckPhoneNumberVerificationCode -> Sem r (Error ∪ Ok))
-> CheckPhoneNumberVerificationCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckPhoneNumberVerificationCode
CheckPhoneNumberVerificationCode T
_1
-- | Sends a code to verify an email address to be added to a user's Telegram Passport 
sendEmailAddressVerificationCode ::
  Member TDLib r =>
  -- | Email address
  T ->
  Sem r (Error  EmailAddressAuthenticationCodeInfo)
sendEmailAddressVerificationCode :: T -> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
sendEmailAddressVerificationCode _1 :: T
_1 = SendEmailAddressVerificationCode
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendEmailAddressVerificationCode
 -> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo))
-> SendEmailAddressVerificationCode
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ T -> SendEmailAddressVerificationCode
SendEmailAddressVerificationCode T
_1
-- | Re-sends the code to verify an email address to be added to a user's Telegram Passport
resendEmailAddressVerificationCode ::
  Member TDLib r =>
  Sem r (Error  EmailAddressAuthenticationCodeInfo)
resendEmailAddressVerificationCode :: Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
resendEmailAddressVerificationCode  = ResendEmailAddressVerificationCode
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendEmailAddressVerificationCode
 -> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo))
-> ResendEmailAddressVerificationCode
-> Sem r (Error ∪ EmailAddressAuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ ResendEmailAddressVerificationCode
ResendEmailAddressVerificationCode 
-- | Checks the email address verification code for Telegram Passport 
checkEmailAddressVerificationCode ::
  Member TDLib r =>
  -- | Verification code
  T ->
  Sem r (Error  Ok)
checkEmailAddressVerificationCode :: T -> Sem r (Error ∪ Ok)
checkEmailAddressVerificationCode _1 :: T
_1 = CheckEmailAddressVerificationCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckEmailAddressVerificationCode -> Sem r (Error ∪ Ok))
-> CheckEmailAddressVerificationCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckEmailAddressVerificationCode
CheckEmailAddressVerificationCode T
_1
-- | Returns a Telegram Passport authorization form for sharing data with a service 
getPassportAuthorizationForm ::
  Member TDLib r =>
  -- | User identifier of the service's bot 
  I32 ->
  -- | Telegram Passport element types requested by the service 
  T ->
  -- | Service's public_key 
  T ->
  -- | Authorization form nonce provided by the service
  T ->
  Sem r (Error  PassportAuthorizationForm)
getPassportAuthorizationForm :: I32 -> T -> T -> T -> Sem r (Error ∪ PassportAuthorizationForm)
getPassportAuthorizationForm _1 :: I32
_1 _2 :: T
_2 _3 :: T
_3 _4 :: T
_4 = GetPassportAuthorizationForm
-> Sem r (Error ∪ PassportAuthorizationForm)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPassportAuthorizationForm
 -> Sem r (Error ∪ PassportAuthorizationForm))
-> GetPassportAuthorizationForm
-> Sem r (Error ∪ PassportAuthorizationForm)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> T -> T -> GetPassportAuthorizationForm
GetPassportAuthorizationForm I32
_1 T
_2 T
_3 T
_4
-- | 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 ::
  Member TDLib r =>
  -- | Authorization form identifier 
  I32 ->
  -- | Password of the current user
  T ->
  Sem r (Error  PassportElementsWithErrors)
getPassportAuthorizationFormAvailableElements :: I32 -> T -> Sem r (Error ∪ PassportElementsWithErrors)
getPassportAuthorizationFormAvailableElements _1 :: I32
_1 _2 :: T
_2 = GetPassportAuthorizationFormAvailableElements
-> Sem r (Error ∪ PassportElementsWithErrors)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetPassportAuthorizationFormAvailableElements
 -> Sem r (Error ∪ PassportElementsWithErrors))
-> GetPassportAuthorizationFormAvailableElements
-> Sem r (Error ∪ PassportElementsWithErrors)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> GetPassportAuthorizationFormAvailableElements
GetPassportAuthorizationFormAvailableElements I32
_1 T
_2
-- | 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 ::
  Member TDLib r =>
  -- | Authorization form identifier 
  I32 ->
  -- | Types of Telegram Passport elements chosen by user to complete the authorization form
  [PassportElementType] ->
  Sem r (Error  Ok)
sendPassportAuthorizationForm :: I32 -> [PassportElementType] -> Sem r (Error ∪ Ok)
sendPassportAuthorizationForm _1 :: I32
_1 _2 :: [PassportElementType]
_2 = SendPassportAuthorizationForm -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendPassportAuthorizationForm -> Sem r (Error ∪ Ok))
-> SendPassportAuthorizationForm -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> [PassportElementType] -> SendPassportAuthorizationForm
SendPassportAuthorizationForm I32
_1 [PassportElementType]
_2
-- | Sends phone number confirmation code. Should be called when user presses "https://t.me/confirmphone?phone=*******&hash=**********" or "tg://confirmphone?phone=*******&hash=**********" link 
sendPhoneNumberConfirmationCode ::
  Member TDLib r =>
  -- | Value of the "hash" parameter from the link
  T ->
  -- | Value of the "phone" parameter from the link 
  T ->
  -- | Settings for the authentication of the user's phone number
  PhoneNumberAuthenticationSettings ->
  Sem r (Error  AuthenticationCodeInfo)
sendPhoneNumberConfirmationCode :: T
-> T
-> PhoneNumberAuthenticationSettings
-> Sem r (Error ∪ AuthenticationCodeInfo)
sendPhoneNumberConfirmationCode _1 :: T
_1 _2 :: T
_2 _3 :: PhoneNumberAuthenticationSettings
_3 = SendPhoneNumberConfirmationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendPhoneNumberConfirmationCode
 -> Sem r (Error ∪ AuthenticationCodeInfo))
-> SendPhoneNumberConfirmationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ T
-> T
-> PhoneNumberAuthenticationSettings
-> SendPhoneNumberConfirmationCode
SendPhoneNumberConfirmationCode T
_1 T
_2 PhoneNumberAuthenticationSettings
_3
-- | Resends phone number confirmation code
resendPhoneNumberConfirmationCode ::
  Member TDLib r =>
  Sem r (Error  AuthenticationCodeInfo)
resendPhoneNumberConfirmationCode :: Sem r (Error ∪ AuthenticationCodeInfo)
resendPhoneNumberConfirmationCode  = ResendPhoneNumberConfirmationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (ResendPhoneNumberConfirmationCode
 -> Sem r (Error ∪ AuthenticationCodeInfo))
-> ResendPhoneNumberConfirmationCode
-> Sem r (Error ∪ AuthenticationCodeInfo)
forall a b. (a -> b) -> a -> b
$ ResendPhoneNumberConfirmationCode
ResendPhoneNumberConfirmationCode 
-- | Checks phone number confirmation code 
checkPhoneNumberConfirmationCode ::
  Member TDLib r =>
  -- | The phone number confirmation code
  T ->
  Sem r (Error  Ok)
checkPhoneNumberConfirmationCode :: T -> Sem r (Error ∪ Ok)
checkPhoneNumberConfirmationCode _1 :: T
_1 = CheckPhoneNumberConfirmationCode -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CheckPhoneNumberConfirmationCode -> Sem r (Error ∪ Ok))
-> CheckPhoneNumberConfirmationCode -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> CheckPhoneNumberConfirmationCode
CheckPhoneNumberConfirmationCode T
_1
-- | Informs the server about the number of pending bot updates if they haven't been processed for a long time; for bots only 
setBotUpdatesStatus ::
  Member TDLib r =>
  -- | The number of pending updates 
  I32 ->
  -- | The last error message
  T ->
  Sem r (Error  Ok)
setBotUpdatesStatus :: I32 -> T -> Sem r (Error ∪ Ok)
setBotUpdatesStatus _1 :: I32
_1 _2 :: T
_2 = SetBotUpdatesStatus -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetBotUpdatesStatus -> Sem r (Error ∪ Ok))
-> SetBotUpdatesStatus -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> SetBotUpdatesStatus
SetBotUpdatesStatus I32
_1 T
_2
-- | Uploads a PNG image with a sticker; for bots only; returns the uploaded file
uploadStickerFile ::
  Member TDLib r =>
  -- | Sticker file owner 
  I32 ->
  -- | PNG image with the sticker; must be up to 512 KB in size and fit in 512x512 square
  InputFile ->
  Sem r (Error  File)
uploadStickerFile :: I32 -> InputFile -> Sem r (Error ∪ File)
uploadStickerFile _1 :: I32
_1 _2 :: InputFile
_2 = UploadStickerFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (UploadStickerFile -> Sem r (Error ∪ File))
-> UploadStickerFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ I32 -> InputFile -> UploadStickerFile
UploadStickerFile I32
_1 InputFile
_2
-- | Creates a new sticker set; for bots only. Returns the newly created sticker set
createNewStickerSet ::
  Member TDLib r =>
  -- | Sticker set owner
  I32 ->
  -- | Sticker set title; 1-64 characters
  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
  T ->
  -- | True, if stickers are masks. Animated stickers can't be masks
  Bool ->
  -- | List of stickers to be added to the set; must be non-empty. All stickers must be of the same type
  [InputSticker] ->
  Sem r (Error  StickerSet)
createNewStickerSet :: I32
-> T -> T -> Bool -> [InputSticker] -> Sem r (Error ∪ StickerSet)
createNewStickerSet _1 :: I32
_1 _2 :: T
_2 _3 :: T
_3 _4 :: Bool
_4 _5 :: [InputSticker]
_5 = CreateNewStickerSet -> Sem r (Error ∪ StickerSet)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (CreateNewStickerSet -> Sem r (Error ∪ StickerSet))
-> CreateNewStickerSet -> Sem r (Error ∪ StickerSet)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> T -> Bool -> [InputSticker] -> CreateNewStickerSet
CreateNewStickerSet I32
_1 T
_2 T
_3 Bool
_4 [InputSticker]
_5
-- | Adds a new sticker to a set; for bots only. Returns the sticker set
addStickerToSet ::
  Member TDLib r =>
  -- | Sticker set owner 
  I32 ->
  -- | Sticker set name 
  T ->
  -- | Sticker to add to the set
  InputSticker ->
  Sem r (Error  StickerSet)
addStickerToSet :: I32 -> T -> InputSticker -> Sem r (Error ∪ StickerSet)
addStickerToSet _1 :: I32
_1 _2 :: T
_2 _3 :: InputSticker
_3 = AddStickerToSet -> Sem r (Error ∪ StickerSet)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddStickerToSet -> Sem r (Error ∪ StickerSet))
-> AddStickerToSet -> Sem r (Error ∪ StickerSet)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> InputSticker -> AddStickerToSet
AddStickerToSet I32
_1 T
_2 InputSticker
_3
-- | Sets a sticker set thumbnail; for bots only. Returns the sticker set
setStickerSetThumbnail ::
  Member TDLib r =>
  -- | Sticker set owner 
  I32 ->
  -- | Sticker set 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
  InputFile ->
  Sem r (Error  StickerSet)
setStickerSetThumbnail :: I32 -> T -> InputFile -> Sem r (Error ∪ StickerSet)
setStickerSetThumbnail _1 :: I32
_1 _2 :: T
_2 _3 :: InputFile
_3 = SetStickerSetThumbnail -> Sem r (Error ∪ StickerSet)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetStickerSetThumbnail -> Sem r (Error ∪ StickerSet))
-> SetStickerSetThumbnail -> Sem r (Error ∪ StickerSet)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> InputFile -> SetStickerSetThumbnail
SetStickerSetThumbnail I32
_1 T
_2 InputFile
_3
-- | 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 ::
  Member TDLib r =>
  -- | Sticker 
  InputFile ->
  -- | New position of the sticker in the set, zero-based
  I32 ->
  Sem r (Error  Ok)
setStickerPositionInSet :: InputFile -> I32 -> Sem r (Error ∪ Ok)
setStickerPositionInSet _1 :: InputFile
_1 _2 :: I32
_2 = SetStickerPositionInSet -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetStickerPositionInSet -> Sem r (Error ∪ Ok))
-> SetStickerPositionInSet -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> I32 -> SetStickerPositionInSet
SetStickerPositionInSet InputFile
_1 I32
_2
-- | Removes a sticker from the set to which it belongs; for bots only. The sticker set must have been created by the bot 
removeStickerFromSet ::
  Member TDLib r =>
  -- | Sticker
  InputFile ->
  Sem r (Error  Ok)
removeStickerFromSet :: InputFile -> Sem r (Error ∪ Ok)
removeStickerFromSet _1 :: InputFile
_1 = RemoveStickerFromSet -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveStickerFromSet -> Sem r (Error ∪ Ok))
-> RemoveStickerFromSet -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ InputFile -> RemoveStickerFromSet
RemoveStickerFromSet InputFile
_1
-- | 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 ::
  Member TDLib r =>
  -- | Location of the map center 
  Location ->
  -- | Map zoom level; 13-20 
  I32 ->
  -- | Map width in pixels before applying scale; 16-1024 
  I32 ->
  -- | Map height in pixels before applying scale; 16-1024 
  I32 ->
  -- | Map scale; 1-3 
  I32 ->
  -- | Identifier of a chat, in which the thumbnail will be shown. Use 0 if unknown
  I53 ->
  Sem r (Error  File)
getMapThumbnailFile :: Location -> I32 -> I32 -> I32 -> I32 -> I32 -> Sem r (Error ∪ File)
getMapThumbnailFile _1 :: Location
_1 _2 :: I32
_2 _3 :: I32
_3 _4 :: I32
_4 _5 :: I32
_5 _6 :: I32
_6 = GetMapThumbnailFile -> Sem r (Error ∪ File)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetMapThumbnailFile -> Sem r (Error ∪ File))
-> GetMapThumbnailFile -> Sem r (Error ∪ File)
forall a b. (a -> b) -> a -> b
$ Location -> I32 -> I32 -> I32 -> I32 -> I32 -> GetMapThumbnailFile
GetMapThumbnailFile Location
_1 I32
_2 I32
_3 I32
_4 I32
_5 I32
_6
-- | Accepts Telegram terms of services 
acceptTermsOfService ::
  Member TDLib r =>
  -- | Terms of service identifier
  T ->
  Sem r (Error  Ok)
acceptTermsOfService :: T -> Sem r (Error ∪ Ok)
acceptTermsOfService _1 :: T
_1 = AcceptTermsOfService -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AcceptTermsOfService -> Sem r (Error ∪ Ok))
-> AcceptTermsOfService -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> AcceptTermsOfService
AcceptTermsOfService T
_1
-- | Sends a custom request; for bots only 
sendCustomRequest ::
  Member TDLib r =>
  -- | The method name 
  T ->
  -- | JSON-serialized method parameters
  T ->
  Sem r (Error  CustomRequestResult)
sendCustomRequest :: T -> T -> Sem r (Error ∪ CustomRequestResult)
sendCustomRequest _1 :: T
_1 _2 :: T
_2 = SendCustomRequest -> Sem r (Error ∪ CustomRequestResult)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SendCustomRequest -> Sem r (Error ∪ CustomRequestResult))
-> SendCustomRequest -> Sem r (Error ∪ CustomRequestResult)
forall a b. (a -> b) -> a -> b
$ T -> T -> SendCustomRequest
SendCustomRequest T
_1 T
_2
-- | Answers a custom query; for bots only 
answerCustomQuery ::
  Member TDLib r =>
  -- | Identifier of a custom query 
  I64 ->
  -- | JSON-serialized answer to the query
  T ->
  Sem r (Error  Ok)
answerCustomQuery :: I64 -> T -> Sem r (Error ∪ Ok)
answerCustomQuery _1 :: I64
_1 _2 :: T
_2 = AnswerCustomQuery -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AnswerCustomQuery -> Sem r (Error ∪ Ok))
-> AnswerCustomQuery -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I64 -> T -> AnswerCustomQuery
AnswerCustomQuery I64
_1 T
_2
-- | Succeeds after a specified amount of time has passed. Can be called before authorization. Can be called before initialization 
setAlarm ::
  Member TDLib r =>
  -- | Number of seconds before the function returns
  Double ->
  Sem r (Error  Ok)
setAlarm :: Double -> Sem r (Error ∪ Ok)
setAlarm _1 :: Double
_1 = SetAlarm -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetAlarm -> Sem r (Error ∪ Ok)) -> SetAlarm -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ Double -> SetAlarm
SetAlarm Double
_1
-- | Uses current user IP address to find their country. Returns two-letter ISO 3166-1 alpha-2 country code. Can be called before authorization
getCountryCode ::
  Member TDLib r =>
  Sem r (Error  Text)
getCountryCode :: Sem r (Error ∪ Text)
getCountryCode  = GetCountryCode -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetCountryCode -> Sem r (Error ∪ Text))
-> GetCountryCode -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ GetCountryCode
GetCountryCode 
-- | Returns the default text for invitation messages to be used as a placeholder when the current user invites friends to Telegram
getInviteText ::
  Member TDLib r =>
  Sem r (Error  Text)
getInviteText :: Sem r (Error ∪ Text)
getInviteText  = GetInviteText -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetInviteText -> Sem r (Error ∪ Text))
-> GetInviteText -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ GetInviteText
GetInviteText 
-- | 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 ::
  Member TDLib r =>
  -- | The link
  T ->
  Sem r (Error  DeepLinkInfo)
getDeepLinkInfo :: T -> Sem r (Error ∪ DeepLinkInfo)
getDeepLinkInfo _1 :: T
_1 = GetDeepLinkInfo -> Sem r (Error ∪ DeepLinkInfo)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetDeepLinkInfo -> Sem r (Error ∪ DeepLinkInfo))
-> GetDeepLinkInfo -> Sem r (Error ∪ DeepLinkInfo)
forall a b. (a -> b) -> a -> b
$ T -> GetDeepLinkInfo
GetDeepLinkInfo T
_1
-- | Returns application config, provided by the server. Can be called before authorization
getApplicationConfig ::
  Member TDLib r =>
  Sem r (Error  JsonValue)
getApplicationConfig :: Sem r (Error ∪ JsonValue)
getApplicationConfig  = GetApplicationConfig -> Sem r (Error ∪ JsonValue)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetApplicationConfig -> Sem r (Error ∪ JsonValue))
-> GetApplicationConfig -> Sem r (Error ∪ JsonValue)
forall a b. (a -> b) -> a -> b
$ GetApplicationConfig
GetApplicationConfig 
-- | Saves application log event on the server. Can be called before authorization 
saveApplicationLogEvent ::
  Member TDLib r =>
  -- | Event type 
  T ->
  -- | Optional chat identifier, associated with the event 
  I53 ->
  -- | The log event data
  JsonValue ->
  Sem r (Error  Ok)
saveApplicationLogEvent :: T -> I32 -> JsonValue -> Sem r (Error ∪ Ok)
saveApplicationLogEvent _1 :: T
_1 _2 :: I32
_2 _3 :: JsonValue
_3 = SaveApplicationLogEvent -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SaveApplicationLogEvent -> Sem r (Error ∪ Ok))
-> SaveApplicationLogEvent -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> JsonValue -> SaveApplicationLogEvent
SaveApplicationLogEvent T
_1 I32
_2 JsonValue
_3
-- | Adds a proxy server for network requests. Can be called before authorization 
addProxy ::
  Member TDLib r =>
  -- | Proxy server IP address 
  T ->
  -- | Proxy server port 
  I32 ->
  -- | True, if the proxy should be enabled 
  Bool ->
  -- | Proxy type
  ProxyType ->
  Sem r (Error  Proxy)
addProxy :: T -> I32 -> Bool -> ProxyType -> Sem r (Error ∪ Proxy)
addProxy _1 :: T
_1 _2 :: I32
_2 _3 :: Bool
_3 _4 :: ProxyType
_4 = AddProxy -> Sem r (Error ∪ Proxy)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddProxy -> Sem r (Error ∪ Proxy))
-> AddProxy -> Sem r (Error ∪ Proxy)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> Bool -> ProxyType -> AddProxy
AddProxy T
_1 I32
_2 Bool
_3 ProxyType
_4
-- | Edits an existing proxy server for network requests. Can be called before authorization 
editProxy ::
  Member TDLib r =>
  -- | Proxy identifier 
  I32 ->
  -- | Proxy server IP address 
  T ->
  -- | Proxy server port 
  I32 ->
  -- | True, if the proxy should be enabled 
  Bool ->
  -- | Proxy type
  ProxyType ->
  Sem r (Error  Proxy)
editProxy :: I32 -> T -> I32 -> Bool -> ProxyType -> Sem r (Error ∪ Proxy)
editProxy _1 :: I32
_1 _2 :: T
_2 _3 :: I32
_3 _4 :: Bool
_4 _5 :: ProxyType
_5 = EditProxy -> Sem r (Error ∪ Proxy)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EditProxy -> Sem r (Error ∪ Proxy))
-> EditProxy -> Sem r (Error ∪ Proxy)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> I32 -> Bool -> ProxyType -> EditProxy
EditProxy I32
_1 T
_2 I32
_3 Bool
_4 ProxyType
_5
-- | Enables a proxy. Only one proxy can be enabled at a time. Can be called before authorization 
enableProxy ::
  Member TDLib r =>
  -- | Proxy identifier
  I32 ->
  Sem r (Error  Ok)
enableProxy :: I32 -> Sem r (Error ∪ Ok)
enableProxy _1 :: I32
_1 = EnableProxy -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (EnableProxy -> Sem r (Error ∪ Ok))
-> EnableProxy -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> EnableProxy
EnableProxy I32
_1
-- | Disables the currently enabled proxy. Can be called before authorization
disableProxy ::
  Member TDLib r =>
  Sem r (Error  Ok)
disableProxy :: Sem r (Error ∪ Ok)
disableProxy  = DisableProxy -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (DisableProxy -> Sem r (Error ∪ Ok))
-> DisableProxy -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ DisableProxy
DisableProxy 
-- | Removes a proxy server. Can be called before authorization 
removeProxy ::
  Member TDLib r =>
  -- | Proxy identifier
  I32 ->
  Sem r (Error  Ok)
removeProxy :: I32 -> Sem r (Error ∪ Ok)
removeProxy _1 :: I32
_1 = RemoveProxy -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (RemoveProxy -> Sem r (Error ∪ Ok))
-> RemoveProxy -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> RemoveProxy
RemoveProxy I32
_1
-- | Returns list of proxies that are currently set up. Can be called before authorization
getProxies ::
  Member TDLib r =>
  Sem r (Error  Proxies)
getProxies :: Sem r (Error ∪ Proxies)
getProxies  = GetProxies -> Sem r (Error ∪ Proxies)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetProxies -> Sem r (Error ∪ Proxies))
-> GetProxies -> Sem r (Error ∪ Proxies)
forall a b. (a -> b) -> a -> b
$ GetProxies
GetProxies 
-- | 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 ::
  Member TDLib r =>
  -- | Proxy identifier
  I32 ->
  Sem r (Error  Text)
getProxyLink :: I32 -> Sem r (Error ∪ Text)
getProxyLink _1 :: I32
_1 = GetProxyLink -> Sem r (Error ∪ Text)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetProxyLink -> Sem r (Error ∪ Text))
-> GetProxyLink -> Sem r (Error ∪ Text)
forall a b. (a -> b) -> a -> b
$ I32 -> GetProxyLink
GetProxyLink I32
_1
-- | Computes time needed to receive a response from a Telegram server through a proxy. Can be called before authorization 
pingProxy ::
  Member TDLib r =>
  -- | Proxy identifier. Use 0 to ping a Telegram server without a proxy
  I32 ->
  Sem r (Error  Seconds)
pingProxy :: I32 -> Sem r (Error ∪ Seconds)
pingProxy _1 :: I32
_1 = PingProxy -> Sem r (Error ∪ Seconds)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (PingProxy -> Sem r (Error ∪ Seconds))
-> PingProxy -> Sem r (Error ∪ Seconds)
forall a b. (a -> b) -> a -> b
$ I32 -> PingProxy
PingProxy I32
_1
-- | Sets new log stream for internal logging of TDLib. This is an offline method. Can be called before authorization. Can be called synchronously 
setLogStream ::
  Member TDLib r =>
  -- | New log stream
  LogStream ->
  Sem r (Error  Ok)
setLogStream :: LogStream -> Sem r (Error ∪ Ok)
setLogStream _1 :: LogStream
_1 = SetLogStream -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetLogStream -> Sem r (Error ∪ Ok))
-> SetLogStream -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ LogStream -> SetLogStream
SetLogStream LogStream
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  LogStream)
getLogStream :: Sem r (Error ∪ LogStream)
getLogStream  = GetLogStream -> Sem r (Error ∪ LogStream)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLogStream -> Sem r (Error ∪ LogStream))
-> GetLogStream -> Sem r (Error ∪ LogStream)
forall a b. (a -> b) -> a -> b
$ GetLogStream
GetLogStream 
-- | 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 ::
  Member TDLib r =>
  -- | 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
  I32 ->
  Sem r (Error  Ok)
setLogVerbosityLevel :: I32 -> Sem r (Error ∪ Ok)
setLogVerbosityLevel _1 :: I32
_1 = SetLogVerbosityLevel -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetLogVerbosityLevel -> Sem r (Error ∪ Ok))
-> SetLogVerbosityLevel -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> SetLogVerbosityLevel
SetLogVerbosityLevel I32
_1
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  LogVerbosityLevel)
getLogVerbosityLevel :: Sem r (Error ∪ LogVerbosityLevel)
getLogVerbosityLevel  = GetLogVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLogVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel))
-> GetLogVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel)
forall a b. (a -> b) -> a -> b
$ GetLogVerbosityLevel
GetLogVerbosityLevel 
-- | 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 ::
  Member TDLib r =>
  Sem r (Error  LogTags)
getLogTags :: Sem r (Error ∪ LogTags)
getLogTags  = GetLogTags -> Sem r (Error ∪ LogTags)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLogTags -> Sem r (Error ∪ LogTags))
-> GetLogTags -> Sem r (Error ∪ LogTags)
forall a b. (a -> b) -> a -> b
$ GetLogTags
GetLogTags 
-- | 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 ::
  Member TDLib r =>
  -- | Logging tag to change verbosity level 
  T ->
  -- | New verbosity level; 1-1024
  I32 ->
  Sem r (Error  Ok)
setLogTagVerbosityLevel :: T -> I32 -> Sem r (Error ∪ Ok)
setLogTagVerbosityLevel _1 :: T
_1 _2 :: I32
_2 = SetLogTagVerbosityLevel -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (SetLogTagVerbosityLevel -> Sem r (Error ∪ Ok))
-> SetLogTagVerbosityLevel -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> SetLogTagVerbosityLevel
SetLogTagVerbosityLevel T
_1 I32
_2
-- | 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 ::
  Member TDLib r =>
  -- | Logging tag to change verbosity level
  T ->
  Sem r (Error  LogVerbosityLevel)
getLogTagVerbosityLevel :: T -> Sem r (Error ∪ LogVerbosityLevel)
getLogTagVerbosityLevel _1 :: T
_1 = GetLogTagVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (GetLogTagVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel))
-> GetLogTagVerbosityLevel -> Sem r (Error ∪ LogVerbosityLevel)
forall a b. (a -> b) -> a -> b
$ T -> GetLogTagVerbosityLevel
GetLogTagVerbosityLevel T
_1
-- | Adds a message to TDLib internal log. This is an offline method. Can be called before authorization. Can be called synchronously
addLogMessage ::
  Member TDLib r =>
  -- | The minimum verbosity level needed for the message to be logged, 0-1023 
  I32 ->
  -- | Text of a message to log
  T ->
  Sem r (Error  Ok)
addLogMessage :: I32 -> T -> Sem r (Error ∪ Ok)
addLogMessage _1 :: I32
_1 _2 :: T
_2 = AddLogMessage -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (AddLogMessage -> Sem r (Error ∪ Ok))
-> AddLogMessage -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ I32 -> T -> AddLogMessage
AddLogMessage I32
_1 T
_2
-- | Does nothing; for testing only. This is an offline method. Can be called before authorization
testCallEmpty ::
  Member TDLib r =>
  Sem r (Error  Ok)
testCallEmpty :: Sem r (Error ∪ Ok)
testCallEmpty  = TestCallEmpty -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallEmpty -> Sem r (Error ∪ Ok))
-> TestCallEmpty -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TestCallEmpty
TestCallEmpty 
-- | Returns the received string; for testing only. This is an offline method. Can be called before authorization 
testCallString ::
  Member TDLib r =>
  -- | String to return
  T ->
  Sem r (Error  TestString)
testCallString :: T -> Sem r (Error ∪ TestString)
testCallString _1 :: T
_1 = TestCallString -> Sem r (Error ∪ TestString)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallString -> Sem r (Error ∪ TestString))
-> TestCallString -> Sem r (Error ∪ TestString)
forall a b. (a -> b) -> a -> b
$ T -> TestCallString
TestCallString T
_1
-- | Returns the received bytes; for testing only. This is an offline method. Can be called before authorization 
testCallBytes ::
  Member TDLib r =>
  -- | Bytes to return
  ByteString64 ->
  Sem r (Error  TestBytes)
testCallBytes :: ByteString64 -> Sem r (Error ∪ TestBytes)
testCallBytes _1 :: ByteString64
_1 = TestCallBytes -> Sem r (Error ∪ TestBytes)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallBytes -> Sem r (Error ∪ TestBytes))
-> TestCallBytes -> Sem r (Error ∪ TestBytes)
forall a b. (a -> b) -> a -> b
$ ByteString64 -> TestCallBytes
TestCallBytes ByteString64
_1
-- | Returns the received vector of numbers; for testing only. This is an offline method. Can be called before authorization 
testCallVectorInt ::
  Member TDLib r =>
  -- | Vector of numbers to return
  [I32] ->
  Sem r (Error  TestVectorInt)
testCallVectorInt :: [I32] -> Sem r (Error ∪ TestVectorInt)
testCallVectorInt _1 :: [I32]
_1 = TestCallVectorInt -> Sem r (Error ∪ TestVectorInt)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallVectorInt -> Sem r (Error ∪ TestVectorInt))
-> TestCallVectorInt -> Sem r (Error ∪ TestVectorInt)
forall a b. (a -> b) -> a -> b
$ [I32] -> TestCallVectorInt
TestCallVectorInt [I32]
_1
-- | Returns the received vector of objects containing a number; for testing only. This is an offline method. Can be called before authorization 
testCallVectorIntObject ::
  Member TDLib r =>
  -- | Vector of objects to return
  [TestInt] ->
  Sem r (Error  TestVectorIntObject)
testCallVectorIntObject :: [TestInt] -> Sem r (Error ∪ TestVectorIntObject)
testCallVectorIntObject _1 :: [TestInt]
_1 = TestCallVectorIntObject -> Sem r (Error ∪ TestVectorIntObject)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallVectorIntObject -> Sem r (Error ∪ TestVectorIntObject))
-> TestCallVectorIntObject -> Sem r (Error ∪ TestVectorIntObject)
forall a b. (a -> b) -> a -> b
$ [TestInt] -> TestCallVectorIntObject
TestCallVectorIntObject [TestInt]
_1
-- | Returns the received vector of strings; for testing only. This is an offline method. Can be called before authorization 
testCallVectorString ::
  Member TDLib r =>
  -- | Vector of strings to return
  [T] ->
  Sem r (Error  TestVectorString)
testCallVectorString :: [T] -> Sem r (Error ∪ TestVectorString)
testCallVectorString _1 :: [T]
_1 = TestCallVectorString -> Sem r (Error ∪ TestVectorString)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallVectorString -> Sem r (Error ∪ TestVectorString))
-> TestCallVectorString -> Sem r (Error ∪ TestVectorString)
forall a b. (a -> b) -> a -> b
$ [T] -> TestCallVectorString
TestCallVectorString [T]
_1
-- | Returns the received vector of objects containing a string; for testing only. This is an offline method. Can be called before authorization 
testCallVectorStringObject ::
  Member TDLib r =>
  -- | Vector of objects to return
  [TestString] ->
  Sem r (Error  TestVectorStringObject)
testCallVectorStringObject :: [TestString] -> Sem r (Error ∪ TestVectorStringObject)
testCallVectorStringObject _1 :: [TestString]
_1 = TestCallVectorStringObject
-> Sem r (Error ∪ TestVectorStringObject)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestCallVectorStringObject
 -> Sem r (Error ∪ TestVectorStringObject))
-> TestCallVectorStringObject
-> Sem r (Error ∪ TestVectorStringObject)
forall a b. (a -> b) -> a -> b
$ [TestString] -> TestCallVectorStringObject
TestCallVectorStringObject [TestString]
_1
-- | Returns the squared received number; for testing only. This is an offline method. Can be called before authorization 
testSquareInt ::
  Member TDLib r =>
  -- | Number to square
  I32 ->
  Sem r (Error  TestInt)
testSquareInt :: I32 -> Sem r (Error ∪ TestInt)
testSquareInt _1 :: I32
_1 = TestSquareInt -> Sem r (Error ∪ TestInt)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestSquareInt -> Sem r (Error ∪ TestInt))
-> TestSquareInt -> Sem r (Error ∪ TestInt)
forall a b. (a -> b) -> a -> b
$ I32 -> TestSquareInt
TestSquareInt I32
_1
-- | Sends a simple network request to the Telegram servers; for testing only. Can be called before authorization
testNetwork ::
  Member TDLib r =>
  Sem r (Error  Ok)
testNetwork :: Sem r (Error ∪ Ok)
testNetwork  = TestNetwork -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestNetwork -> Sem r (Error ∪ Ok))
-> TestNetwork -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TestNetwork
TestNetwork 
-- | Sends a simple network request to the Telegram servers via proxy; for testing only. Can be called before authorization 
testProxy ::
  Member TDLib r =>
  -- | Proxy server IP address 
  T ->
  -- | Proxy server port 
  I32 ->
  -- | Proxy type
  ProxyType ->
  -- | Identifier of a datacenter, with which to test connection 
  I32 ->
  -- | The maximum overall timeout for the request
  Double ->
  Sem r (Error  Ok)
testProxy :: T -> I32 -> ProxyType -> I32 -> Double -> Sem r (Error ∪ Ok)
testProxy _1 :: T
_1 _2 :: I32
_2 _3 :: ProxyType
_3 _4 :: I32
_4 _5 :: Double
_5 = TestProxy -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestProxy -> Sem r (Error ∪ Ok))
-> TestProxy -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ T -> I32 -> ProxyType -> I32 -> Double -> TestProxy
TestProxy T
_1 I32
_2 ProxyType
_3 I32
_4 Double
_5
-- | Forces an updates.getDifference call to the Telegram servers; for testing only
testGetDifference ::
  Member TDLib r =>
  Sem r (Error  Ok)
testGetDifference :: Sem r (Error ∪ Ok)
testGetDifference  = TestGetDifference -> Sem r (Error ∪ Ok)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestGetDifference -> Sem r (Error ∪ Ok))
-> TestGetDifference -> Sem r (Error ∪ Ok)
forall a b. (a -> b) -> a -> b
$ TestGetDifference
TestGetDifference 
-- | Does nothing and ensures that the Update object is used; for testing only. This is an offline method. Can be called before authorization
testUseUpdate ::
  Member TDLib r =>
  Sem r (Error  Update)
testUseUpdate :: Sem r (Error ∪ Update)
testUseUpdate  = TestUseUpdate -> Sem r (Error ∪ Update)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestUseUpdate -> Sem r (Error ∪ Update))
-> TestUseUpdate -> Sem r (Error ∪ Update)
forall a b. (a -> b) -> a -> b
$ TestUseUpdate
TestUseUpdate 
-- | 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 ::
  Member TDLib r =>
  -- | The error to be returned
  Error ->
  Sem r (Error  Error)
testReturnError :: Error -> Sem r (Error ∪ Error)
testReturnError _1 :: Error
_1 = TestReturnError -> Sem r (Error ∪ Error)
forall cmd res (r :: [(* -> *) -> * -> *]).
(ToJSON cmd, FromJSON res, Member TDLib r) =>
cmd -> Sem r res
runCmd (TestReturnError -> Sem r (Error ∪ Error))
-> TestReturnError -> Sem r (Error ∪ Error)
forall a b. (a -> b) -> a -> b
$ Error -> TestReturnError
TestReturnError Error
_1